From: sparky4 <sparky4@cock.li>
Date: Sat, 7 Oct 2023 20:28:13 +0000 (-0500)
Subject: extrcted keen code remake
X-Git-Url: http://4ch.mooo.com/gitweb/?a=commitdiff_plain;h=7d1948e210bb7b58af0a0412e71f2a0a0a2010af;p=16.git

extrcted keen code remake
---

diff --git a/16/keen456/KEEN4-6/-ID_VW_AE.ASM b/16/keen456/KEEN4-6/-ID_VW_AE.ASM
new file mode 100755
index 00000000..4e76e86a
--- /dev/null
+++ b/16/keen456/KEEN4-6/-ID_VW_AE.ASM
@@ -0,0 +1,1832 @@
+; Reconstructed Commander Keen 4-6 Source Code
+; Copyright (C) 2021 K1n9_Duk3
+;
+; This file is primarily based on:
+; Catacomb 3-D Source Code
+; Copyright (C) 1993-2014 Flat Rock Software
+;
+; This program is free software; you can redistribute it and/or modify
+; it under the terms of the GNU General Public License as published by
+; the Free Software Foundation; either version 2 of the License, or
+; (at your option) any later version.
+;
+; This program is distributed in the hope that it will be useful,
+; but WITHOUT ANY WARRANTY; without even the implied warranty of
+; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+; GNU General Public License for more details.
+;
+; You should have received a copy of the GNU General Public License along
+; with this program; if not, write to the Free Software Foundation, Inc.,
+; 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+
+;=================================
+;
+; EGA view manager routines
+;
+;=================================
+
+;============================================================================
+;
+; All EGA drawing routines that write out words need to have alternate forms
+; for starting on even and odd addresses, because writing a word at segment
+; offset 0xffff causes an exception!  To work around this, write a single
+; byte out to make the address even, so it wraps cleanly at the end.
+;
+; All of these routines assume read/write mode 0, and will allways return
+; in that state.
+; The direction flag should be clear
+; readmap/writemask is left in an undefined state
+;
+;============================================================================
+
+
+;============================================================================
+;
+; VW_Plot (int x,y,color)
+;
+;============================================================================
+
+DATASEG
+
+plotpixels	db	128,64,32,16,8,4,2,1
+
+CODESEG
+
+PROC	VW_Plot x:WORD, y:WORD, color:WORD
+PUBLIC	VW_Plot
+USES	SI,DI
+
+	mov	es,[screenseg]
+
+	mov	dx,SC_INDEX
+	mov	ax,SC_MAPMASK+15*256
+	WORDOUT
+
+	mov	dx,GC_INDEX
+	mov	ax,GC_MODE+2*256	;write mode 2
+	WORDOUT
+
+	mov	di,[bufferofs]
+	mov	bx,[y]
+	shl	bx,1
+	add	di,[ylookup+bx]
+	mov	bx,[x]
+	mov	ax,bx
+	shr	ax,1
+	shr	ax,1
+	shr	ax,1
+	add	di,ax				; di = byte on screen
+
+	and	bx,7
+	mov	ah,[plotpixels+bx]
+	mov	al,GC_BITMASK		;mask off other pixels
+	WORDOUT
+
+	mov		bl,[BYTE color]
+	xchg	bl,[es:di]		; load latches and write pixel
+
+	mov	dx,GC_INDEX
+	mov	ah,0ffh				;no bit mask
+	WORDOUT
+	mov	ax,GC_MODE+0*256	;write mode 0
+	WORDOUT
+
+	ret
+
+ENDP
+
+
+;============================================================================
+;
+; VW_Vlin (int yl,yh,x,color)
+;
+;============================================================================
+
+PROC	VW_Vlin yl:WORD, yh:WORD, x:WORD, color:WORD
+PUBLIC	VW_Vlin
+USES	SI,DI
+
+	mov	es,[screenseg]
+
+	mov	dx,SC_INDEX
+	mov	ax,SC_MAPMASK+15*256
+	WORDOUT
+
+	mov	dx,GC_INDEX
+	mov	ax,GC_MODE+2*256	;write mode 2
+	WORDOUT
+
+	mov	di,[bufferofs]
+	mov	bx,[yl]
+	shl	bx,1
+	add	di,[ylookup+bx]
+	mov	bx,[x]
+	mov	ax,bx
+	shr	ax,1
+	shr	ax,1
+	shr	ax,1
+	add	di,ax				; di = byte on screen
+
+	and	bx,7
+	mov	ah,[plotpixels+bx]
+	mov	al,GC_BITMASK		;mask off other pixels
+	WORDOUT
+
+	mov	cx,[yh]
+	sub	cx,[yl]
+	inc	cx					;number of pixels to plot
+
+	mov	bh,[BYTE color]
+	mov	dx,[linewidth]
+
+@@plot:
+	mov		bl,bh
+	xchg	bl,[es:di]		; load latches and write pixel
+	add		di,dx
+
+	loop	@@plot
+
+	mov	dx,GC_INDEX
+	mov	ah,0ffh				;no bit mask
+	WORDOUT
+	mov	ax,GC_MODE+0*256	;write mode 0
+	WORDOUT
+
+	ret
+
+ENDP
+
+
+;============================================================================
+
+
+;===================
+;
+; VW_DrawTile8
+;
+; xcoord in bytes (8 pixels), ycoord in pixels
+; All Tile8s are in one grseg, so an offset is calculated inside it
+;
+;===================
+
+PROC	VW_DrawTile8	xcoord:WORD, ycoord:WORD, tile:WORD
+PUBLIC	VW_DrawTile8
+USES	SI,DI
+
+	mov	es,[screenseg]
+
+	mov	di,[bufferofs]
+	add	di,[xcoord]
+	mov	bx,[ycoord]
+	shl	bx,1
+	add	di,[ylookup+bx]
+	mov	[ss:screendest],di		;screen destination
+
+	mov	bx,[linewidth]
+	dec	bx
+
+	mov	si,[tile]
+	shl	si,1
+	shl	si,1
+	shl	si,1
+	shl	si,1
+	shl	si,1
+
+	mov	ds,[grsegs+STARTTILE8*2] ; segment for all tile8s
+
+	mov	cx,4					;planes to draw
+	mov	ah,0001b				;map mask
+
+	mov	dx,SC_INDEX
+	mov	al,SC_MAPMASK
+
+;
+; start drawing
+;
+
+@@planeloop:
+	WORDOUT
+	shl	ah,1					;shift plane mask over for next plane
+
+	mov	di,[ss:screendest]		;start at same place in all planes
+
+REPT	7
+	movsb
+	add	di,bx
+ENDM
+	movsb
+
+	loop	@@planeloop
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+ENDP
+
+
+;============================================================================
+;
+; VW_MaskBlock
+;
+; Draws a masked block shape to the screen.  bufferofs is NOT accounted for.
+; The mask comes first, then four planes of data.
+;
+;============================================================================
+
+DATASEG
+
+UNWOUNDMASKS	=	10
+
+
+maskroutines	dw	mask0,mask0,mask1E,mask1E,mask2E,mask2O,mask3E,mask3O
+				dw	mask4E,mask4O,mask5E,mask5O,mask6E,mask6O
+				dw	mask7E,mask7O,mask8E,mask8O,mask9E,mask9O
+				dw	mask10E,mask10O
+
+
+routinetouse	dw	?
+
+CODESEG
+
+PROC	VW_MaskBlock	segm:WORD, ofs:WORD, dest:WORD, wide:WORD, height:WORD, planesize:WORD
+PUBLIC	VW_MaskBlock
+USES	SI,DI
+
+	mov	es,[screenseg]
+
+	mov	[BYTE planemask],1
+	mov	[BYTE planenum],0
+
+	mov	di,[wide]
+	mov	dx,[linewidth]
+	sub	dx,[wide]
+	mov	[linedelta],dx			;amount to add after drawing each line
+
+	mov	bx,[planesize]			; si+bx = data location
+
+	cmp	di,UNWOUNDMASKS
+	jbe	@@unwoundroutine
+	mov	[routinetouse],OFFSET generalmask
+	jmp	NEAR @@startloop
+
+;=================
+;
+; use the unwound routines
+;
+;=================
+
+@@unwoundroutine:
+	mov	cx,[dest]
+	shr	cx,1
+	rcl	di,1					;shift a 1 in if destination is odd
+	shl	di,1					;to index into a word width table
+	mov	ax,[maskroutines+di]	;call the right routine
+	mov	[routinetouse],ax
+
+@@startloop:
+	mov	ds,[segm]
+
+@@drawplane:
+	mov	dx,SC_INDEX
+	mov	al,SC_MAPMASK
+	mov	ah,[ss:planemask]
+	WORDOUT
+	mov	dx,GC_INDEX
+	mov	al,GC_READMAP
+	mov	ah,[ss:planenum]
+	WORDOUT
+
+	mov	si,[ofs]				;start back at the top of the mask
+	mov	di,[dest]				;start at same place in all planes
+	mov	cx,[height]				;scan lines to draw
+	mov dx,[ss:linedelta]
+
+	jmp [ss:routinetouse]		;draw one plane
+planereturn:					;routine jmps back here
+
+	add	bx,[ss:planesize]		;start of mask = start of next plane
+
+	inc	[ss:planenum]
+	shl	[ss:planemask],1		;shift plane mask over for next plane
+	cmp	[ss:planemask],10000b	;done all four planes?
+	jne	@@drawplane
+
+mask0:
+	mov	ax,ss
+	mov	ds,ax
+	ret							;width of 0 = no drawing
+
+;==============
+;
+; General purpose masked block drawing.  This could be optimised into
+; four routines to use words, but few play loop sprites should be this big!
+;
+;==============
+
+generalmask:
+	mov	dx,cx
+
+@@lineloopgen:
+	mov	cx,[wide]
+@@byteloop:
+	mov	al,[es:di]
+	and	al,[si]
+	or	al,[bx+si]
+	inc	si
+	stosb
+	loop	@@byteloop
+
+	add	di,[ss:linedelta]
+	dec	dx
+	jnz	@@lineloopgen
+	jmp	planereturn
+
+;=================
+;
+; Horizontally unwound routines to draw certain masked blocks faster
+;
+;=================
+
+MACRO	MASKBYTE
+	lodsb
+	and	al,[es:di]
+	or	al,[bx+si-1]
+	stosb
+ENDM
+
+MACRO	MASKWORD
+	lodsw
+	and	ax,[es:di]
+	or	ax,[bx+si-2]
+	stosw
+ENDM
+
+MACRO	SPRITELOOP	addr
+	add	di,dx
+	loop	addr
+	jmp	planereturn
+ENDM
+
+
+EVEN
+mask1E:
+	MASKBYTE
+	SPRITELOOP	mask1E
+
+EVEN
+mask2E:
+	MASKWORD
+	SPRITELOOP	mask2E
+
+EVEN
+mask2O:
+	MASKBYTE
+	MASKBYTE
+	SPRITELOOP	mask2O
+
+EVEN
+mask3E:
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask3E
+
+EVEN
+mask3O:
+	MASKBYTE
+	MASKWORD
+	SPRITELOOP	mask3O
+
+EVEN
+mask4E:
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask4E
+
+EVEN
+mask4O:
+	MASKBYTE
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask4O
+
+EVEN
+mask5E:
+	MASKWORD
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask5E
+
+EVEN
+mask5O:
+	MASKBYTE
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask5O
+
+EVEN
+mask6E:
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask6E
+
+EVEN
+mask6O:
+	MASKBYTE
+	MASKWORD
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask6O
+
+EVEN
+mask7E:
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask7E
+
+EVEN
+mask7O:
+	MASKBYTE
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask7O
+
+EVEN
+mask8E:
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask8E
+
+EVEN
+mask8O:
+	MASKBYTE
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask8O
+
+EVEN
+mask9E:
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask9E
+
+EVEN
+mask9O:
+	MASKBYTE
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask9O
+
+EVEN
+mask10E:
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask10E
+
+EVEN
+mask10O:
+	MASKBYTE
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask10O
+
+
+ENDP
+
+
+;============================================================================
+;
+; VW_InverseMask
+;
+; Draws a masked block shape to the screen.  bufferofs is NOT accounted for.
+; The mask comes first, then four planes of data.
+;
+;============================================================================
+
+PROC	VW_InverseMask	segm:WORD, ofs:WORD, dest:WORD, wide:WORD, height:WORD
+PUBLIC	VW_InverseMask
+USES	SI,DI
+
+	mov	dx,SC_INDEX
+	mov	ax,SC_MAPMASK+15*256
+	WORDOUT
+	mov	dx,GC_INDEX
+	mov	ax,GC_DATAROTATE+16*256		;set function = OR
+	WORDOUT
+
+	mov	es, [screenseg]
+	mov	ax, [wide]
+	mov	dx, [linewidth]
+	sub	dx, ax;
+	mov	ds, [segm]
+	mov	si, [ofs]
+	mov	di, [dest]
+	mov	bx, [height]
+@@yloop:
+	mov	cx, [wide]
+@@xloop:
+	lodsb
+	not	al
+	xchg	al, [es:di]
+	inc	di
+	loop	@@xloop
+	add	di, dx
+	dec	bx
+	jnz	@@yloop
+
+	mov	dx,GC_INDEX
+	mov	ax,GC_DATAROTATE+0*256		;set function = no change
+	WORDOUT
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+ENDP
+
+;============================================================================
+;
+; VW_ScreenToScreen
+;
+; Basic block copy routine.  Copies one block of screen memory to another,
+; using write mode 1 (sets it and returns with write mode 0).  bufferofs is
+; NOT accounted for.
+;
+;============================================================================
+
+PROC	VW_ScreenToScreen	source:WORD, dest:WORD, wide:WORD, height:WORD
+PUBLIC	VW_ScreenToScreen
+USES	SI,DI
+
+	pushf
+	cli
+
+	mov	dx,SC_INDEX
+	mov	ax,SC_MAPMASK+15*256
+	WORDOUT
+	mov	dx,GC_INDEX
+	mov	ax,GC_MODE+1*256
+	WORDOUT
+
+	popf
+
+	mov	bx,[linewidth]
+	sub	bx,[wide]
+
+	mov	ax,[screenseg]
+	mov	es,ax
+	mov	ds,ax
+
+	mov	si,[source]
+	mov	di,[dest]				;start at same place in all planes
+	mov	dx,[height]				;scan lines to draw
+	mov	ax,[wide]
+
+@@lineloop:
+	mov	cx,ax
+	rep	movsb
+	add	si,bx
+	add	di,bx
+
+	dec	dx
+	jnz	@@lineloop
+
+	mov	dx,GC_INDEX
+	mov	ax,GC_MODE+0*256
+	WORDOUT
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+ENDP
+
+
+;============================================================================
+;
+; VW_MemToScreen
+;
+; Basic block drawing routine. Takes a block shape at segment pointer source
+; with four planes of width by height data, and draws it to dest in the
+; virtual screen, based on linewidth.  bufferofs is NOT accounted for.
+; There are four drawing routines to provide the best optimized code while
+; accounting for odd segment wrappings due to the floating screens.
+;
+;============================================================================
+
+DATASEG
+
+memtoscreentable	dw	eventoeven,eventoodd,oddtoeven,oddtoodd
+
+CODESEG
+
+
+PROC	VW_MemToScreen	source:WORD, dest:WORD, wide:WORD, height:WORD
+PUBLIC	VW_MemToScreen
+USES	SI,DI
+
+	mov	es,[screenseg]
+
+	mov	bx,[linewidth]
+	sub	bx,[wide]
+
+	mov	ds,[source]
+
+
+	xor	si,si					;block is segment aligned
+
+	xor	di,di
+	shr	[wide],1				;change wide to words, and see if carry is set
+	rcl	di,1					;1 if wide is odd
+	mov	ax,[dest]
+	shr	ax,1
+	rcl	di,1					;shift a 1 in if destination is odd
+	shl	di,1					;to index into a word width table
+	mov	ax,SC_MAPMASK+0001b*256	;map mask for plane 0
+	jmp	[ss:memtoscreentable+di]	;call the right routine
+
+;==============
+;
+; Copy an even width block to an even video address
+;
+;==============
+
+eventoeven:
+	mov	dx,SC_INDEX
+	WORDOUT
+
+	mov	di,[dest]				;start at same place in all planes
+	mov	dx,[height]				;scan lines to draw
+
+@@lineloopEE:
+	mov	cx,[wide]
+	rep	movsw
+
+	add	di,bx
+
+	dec	dx
+	jnz	@@lineloopEE
+
+	shl	ah,1					;shift plane mask over for next plane
+	cmp	ah,10000b				;done all four planes?
+	jne	eventoeven
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+;==============
+;
+; Copy an odd width block to an even video address
+;
+;==============
+
+oddtoeven:
+	mov	dx,SC_INDEX
+	WORDOUT
+
+	mov	di,[dest]				;start at same place in all planes
+	mov	dx,[height]				;scan lines to draw
+
+@@lineloopOE:
+	mov	cx,[wide]
+	rep	movsw
+	movsb						;copy the last byte
+
+	add	di,bx
+
+	dec	dx
+	jnz	@@lineloopOE
+
+	shl	ah,1					;shift plane mask over for next plane
+	cmp	ah,10000b				;done all four planes?
+	jne	oddtoeven
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+;==============
+;
+; Copy an even width block to an odd video address
+;
+;==============
+
+eventoodd:
+	dec	[wide]					;one word has to be handled seperately
+EOplaneloop:
+	mov	dx,SC_INDEX
+	WORDOUT
+
+	mov	di,[dest]				;start at same place in all planes
+	mov	dx,[height]				;scan lines to draw
+
+@@lineloopEO:
+	movsb
+	mov	cx,[wide]
+	rep	movsw
+	movsb
+
+	add	di,bx
+
+	dec	dx
+	jnz	@@lineloopEO
+
+	shl	ah,1					;shift plane mask over for next plane
+	cmp	ah,10000b				;done all four planes?
+	jne	EOplaneloop
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+;==============
+;
+; Copy an odd width block to an odd video address
+;
+;==============
+
+oddtoodd:
+	mov	dx,SC_INDEX
+	WORDOUT
+
+	mov	di,[dest]				;start at same place in all planes
+	mov	dx,[height]				;scan lines to draw
+
+@@lineloopOO:
+	movsb
+	mov	cx,[wide]
+	rep	movsw
+
+	add	di,bx
+
+	dec	dx
+	jnz	@@lineloopOO
+
+	shl	ah,1					;shift plane mask over for next plane
+	cmp	ah,10000b				;done all four planes?
+	jne	oddtoodd
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+
+ENDP
+
+;===========================================================================
+;
+; VW_ScreenToMem
+;
+; Copies a block of video memory to main memory, in order from planes 0-3.
+; This could be optimized along the lines of VW_MemToScreen to take advantage
+; of word copies, but this is an infrequently called routine.
+;
+;===========================================================================
+
+PROC	VW_ScreenToMem	source:WORD, dest:WORD, wide:WORD, height:WORD
+PUBLIC	VW_ScreenToMem
+USES	SI,DI
+
+	mov	es,[dest]
+
+	mov	bx,[linewidth]
+	sub	bx,[wide]
+
+	mov	ds,[screenseg]
+
+	mov	ax,GC_READMAP			;read map for plane 0
+
+	xor	di,di
+
+@@planeloop:
+	mov	dx,GC_INDEX
+	WORDOUT
+
+	mov	si,[source]				;start at same place in all planes
+	mov	dx,[height]				;scan lines to draw
+
+@@lineloop:
+	mov	cx,[wide]
+	rep	movsb
+
+	add	si,bx
+
+	dec	dx
+	jnz	@@lineloop
+
+	inc	ah
+	cmp	ah,4					;done all four planes?
+	jne	@@planeloop
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+ENDP
+
+
+;============================================================================
+;
+; VWL_UpdateScreenBlocks
+;
+; Scans through the update matrix and copies any areas that have changed
+; to the visable screen, then zeros the update array
+;
+;============================================================================
+
+
+
+; AX	0/1 for scasb, temp for segment register transfers
+; BX    width for block copies
+; CX	REP counter
+; DX	line width deltas
+; SI	source for copies
+; DI	scas dest / movsb dest
+; BP	pointer to end of bufferblocks
+
+PROC	VWL_UpdateScreenBlocks
+PUBLIC	VWL_UpdateScreenBlocks
+USES	SI,DI,BP
+
+	jmp	SHORT @@realstart
+@@done:
+;
+; all tiles have been scanned
+;
+	mov	dx,GC_INDEX				; restore write mode 0
+	mov	ax,GC_MODE+0*256
+	WORDOUT
+
+	xor	ax,ax					; clear out the update matrix
+	mov	cx,UPDATEWIDE*UPDATEHIGH/2
+
+	mov	di,[updateptr]
+	rep	stosw
+
+	ret
+
+@@realstart:
+	mov	dx,SC_INDEX
+	mov	ax,SC_MAPMASK+15*256
+	WORDOUT
+	mov	dx,GC_INDEX
+	mov	ax,GC_MODE+1*256
+	WORDOUT
+
+	mov	di,[updateptr]			; start of floating update screen
+	mov	bp,di
+	add	bp,UPDATEWIDE*UPDATEHIGH+1 ; when di = bp, all tiles have been scanned
+
+	push	di
+	mov	cx,-1					; definately scan the entire thing
+
+;
+; scan for a 1 in the update list, meaning a tile needs to be copied
+; from the master screen to the current screen
+;
+@@findtile:
+	pop	di						; place to continue scaning from
+	mov	ax,ss
+	mov	es,ax					; search in the data segment
+	mov	ds,ax
+	mov al,1
+	repne	scasb
+	cmp	di,bp
+	jae	@@done
+
+	cmp	[BYTE di],al
+	jne	@@singletile
+	jmp	@@tileblock
+
+;============
+;
+; copy a single tile
+;
+;============
+@@singletile:
+	inc	di						; we know the next tile is nothing
+	push	di					; save off the spot being scanned
+	sub	di,[updateptr]
+	shl	di,1
+	mov	di,[blockstarts-4+di]	; start of tile location on screen
+	mov	si,di
+	add	si,[bufferofs]
+	add	di,[displayofs]
+
+	mov	dx,[linewidth]
+	sub	dx,2
+	mov	ax,[screenseg]
+	mov	ds,ax
+	mov	es,ax
+
+REPT	15
+	movsb
+	movsb
+	add	si,dx
+	add	di,dx
+ENDM
+	movsb
+	movsb
+
+	jmp	@@findtile
+
+;============
+;
+; more than one tile in a row needs to be updated, so do it as a group
+;
+;============
+EVEN
+@@tileblock:
+	mov	dx,di					; hold starting position + 1 in dx
+	inc	di						; we know the next tile also gets updated
+	repe	scasb				; see how many more in a row
+	push	di					; save off the spot being scanned
+
+	mov	bx,di
+	sub	bx,dx					; number of tiles in a row
+	shl	bx,1					; number of bytes / row
+
+	mov	di,dx					; lookup position of start tile
+	sub	di,[updateptr]
+	shl	di,1
+	mov	di,[blockstarts-2+di]	; start of tile location
+	mov	si,di
+	add	si,[bufferofs]
+	add	di,[displayofs]
+
+	mov	dx,[linewidth]
+	sub	dx,bx					; offset to next line on screen
+
+	mov	ax,[screenseg]
+	mov	ds,ax
+	mov	es,ax
+
+REPT	15
+	mov	cx,bx
+	rep	movsb
+	add	si,dx
+	add	di,dx
+ENDM
+	mov	cx,bx
+	rep	movsb
+
+	dec	cx						; was 0 from last rep movsb, now $ffff for scasb
+	jmp	@@findtile
+
+ENDP
+
+
+;===========================================================================
+;
+;                    MISC EGA ROUTINES
+;
+;===========================================================================
+
+;=================
+;
+; VWL_WaitRetrace
+;
+;=================
+
+DATASEG
+
+EXTRN	TimeCount			:DWORD
+EXTRN	jerk			:WORD
+EXTRN	nopan				:WORD
+
+CODESEG
+
+PROC	VWL_WaitRetrace	NEAR
+	mov	dx,STATUS_REGISTER_1
+	mov	bx,[WORD TimeCount]
+@@waitloop:
+	sti
+	jmp	$+2
+	cli
+
+	in	al,dx
+	test	al,8
+	jnz	@@done
+	mov	ax,[WORD TimeCount]
+	sub	ax,bx
+	cmp	ax,1
+	jbe	@@waitloop
+
+@@done:
+	ret
+ENDP
+
+
+;==============
+;
+; VW_SetScreen
+;
+;==============
+
+PROC	VW_SetScreen  crtc:WORD, pel:WORD
+PUBLIC	VW_SetScreen
+
+if waitforvbl
+
+	mov	dx,STATUS_REGISTER_1
+
+;
+; wait util the CRTC just starts scaning a diplayed line to set the CRTC start
+;
+	cli
+
+@@waitnodisplay:
+	in	al,dx
+	test	al,01b
+	jz	@@waitnodisplay
+
+@@waitdisplay:
+	in	al,dx
+	test	al,01b
+	jnz	@@waitdisplay
+
+endif
+
+;
+; set CRTC start
+;
+; for some reason, my XT's EGA card doesn't like word outs to the CRTC
+; index...
+;
+	mov	cx,[crtc]
+	mov	dx,CRTC_INDEX
+	mov	al,0ch		;start address high register
+	out	dx,al
+	inc	dx
+	mov	al,ch
+	out	dx,al
+	dec	dx
+	mov	al,0dh		;start address low register
+	out	dx,al
+	mov	al,cl
+	inc	dx
+	out	dx,al
+
+	test	[jerk],1
+	jz	@@l3
+	call	VWL_WaitRetrace
+
+@@l3:
+	test	[nopan],1
+	jnz	@@l4
+;
+; set horizontal panning
+;
+
+	mov	dx,ATR_INDEX
+	mov	al,ATR_PELPAN or 20h
+	out	dx,al
+	jmp	$+2
+	mov	al,[BYTE pel]		;pel pan value
+	out	dx,al
+
+@@l4:
+	test	[jerk],1
+	jnz	@@done
+	call	VWL_WaitRetrace
+
+@@done:
+	sti
+
+	ret
+
+ENDP
+
+
+if NUMFONT+NUMFONTM
+
+;===========================================================================
+;
+; GENERAL FONT DRAWING ROUTINES
+;
+;===========================================================================
+
+DATASEG
+
+px	dw	?					; proportional character drawing coordinates
+py	dw	?
+pdrawmode	db	11000b		; 8 = OR, 24 = XOR, put in GC_DATAROTATE
+fontcolor	db	15		;0-15 mapmask value
+
+PUBLIC	px,py,pdrawmode,fontcolor
+
+;
+; offsets in font structure
+;
+pcharheight	=	0		;lines high
+charloc		=	2		;pointers to every character
+charwidth	=	514		;every character's width in pixels
+
+
+propchar	dw	?			; the character number to shift
+stringptr	dw	?,?
+
+
+BUFFWIDTH	=	50
+BUFFHEIGHT	=   32			; must be twice as high as font for masked fonts
+
+databuffer	db	BUFFWIDTH*BUFFHEIGHT dup (?)
+
+bufferwidth	dw	?						; bytes with valid info / line
+bufferheight dw	?						; number of lines currently used
+
+bufferbyte	dw	?
+bufferbit	dw	?
+
+screenspot	dw	?						; where the buffer is going
+
+bufferextra	dw	?						; add at end of a line copy
+screenextra	dw	?
+
+PUBLIC	bufferwidth,bufferheight,screenspot
+
+CODESEG
+
+;======================
+;
+; Macros to table shift a byte of font
+;
+;======================
+
+MACRO	SHIFTNOXOR
+	mov	al,[es:bx]		; source
+	xor	ah,ah
+	shl	ax,1
+	mov	si,ax
+	mov	ax,[bp+si]		; table shift into two bytes
+	or	[di],al			; or with first byte
+	inc	di
+	mov	[di],ah			; replace next byte
+	inc	bx				; next source byte
+ENDM
+
+MACRO	SHIFTWITHXOR
+	mov	al,[es:bx]		; source
+	xor	ah,ah
+	shl	ax,1
+	mov	si,ax
+	mov	ax,[bp+si]		; table shift into two bytes
+	not	ax
+	and	[di],al			; and with first byte
+	inc	di
+	mov	[di],ah			; replace next byte
+	inc	bx				; next source byte
+ENDM
+
+
+;=======================
+;
+; BufferToScreen
+;
+; Pass buffer start in SI (somewhere in databuffer)
+; Draws the buffer to the EGA screen in the current write mode
+;
+;========================
+
+PROC	BufferToScreen	NEAR
+
+	mov	es,[screenseg]
+	mov	di,[screenspot]
+
+	mov	bx,[bufferwidth]		;calculate offsets for end of each line
+	or	bx,bx
+	jnz	@@isthere
+	ret							;nothing to draw
+
+@@isthere:
+	mov	ax,[linewidth]
+	sub	ax,bx
+	mov	[screenextra],ax
+	mov	ax,BUFFWIDTH
+	sub	ax,bx
+	mov	[bufferextra],ax
+
+	mov	bx,[bufferheight]		;lines to copy
+@@lineloop:
+	mov	cx,[bufferwidth]		;bytes to copy
+@@byteloop:
+	lodsb						;get a byte from the buffer
+	xchg	[es:di],al			;load latches and store back to screen
+	inc	di
+
+	loop	@@byteloop
+
+	add	si,[bufferextra]
+	add	di,[screenextra]
+
+	dec	bx
+	jnz	@@lineloop
+
+	ret
+ENDP
+
+
+;============================================================================
+;
+; NON MASKED FONT DRAWING ROUTINES
+;
+;============================================================================
+
+if numfont
+
+DATASEG
+
+shiftdrawtable	dw      0,shift1wide,shift2wide,shift3wide,shift4wide
+				dw		shift5wide
+
+CODESEG
+
+;==================
+;
+; ShiftPropChar
+;
+; Call with BX = character number (0-255)
+; Draws one character to the buffer at bufferbyte/bufferbit, and adjusts
+; them to the new position
+;
+;==================
+
+PROC	ShiftPropChar	NEAR
+
+	mov	si,[fontnumber]
+	shl	si,1
+	mov	es,[grsegs+STARTFONT*2+si]	;segment of font to use
+
+;
+; find character location, width, and height
+;
+	mov	si,[es:charwidth+bx]
+	and	si,0ffh					;SI hold width in pixels
+	shl	bx,1
+	mov	bx,[es:charloc+bx]		;BX holds pointer to character data
+
+;
+; look up which shift table to use, based on bufferbit
+;
+	mov	di,[bufferbit]
+	shl	di,1
+	mov	bp,[shifttabletable+di]	;BP holds pointer to shift table
+
+	mov	di,OFFSET databuffer
+	add	di,[bufferbyte]			;DI holds pointer to buffer
+
+;
+; advance position by character width
+;
+	mov	cx,[bufferbit]
+	add	cx,si					;new bit position
+	mov	ax,cx
+	and	ax,7
+	mov	[bufferbit],ax			;new bit position
+	mov	ax,cx
+	shr	ax,1
+	shr	ax,1
+	shr	ax,1
+	add	[bufferbyte],ax			;new byte position
+
+	add	si,7
+	shr	si,1
+	shr	si,1
+	shr	si,1					;bytes the character is wide
+	shl	si,1                    ;*2 to look up in shiftdrawtable
+
+	mov	cx,[es:pcharheight]
+	mov	dx,BUFFWIDTH
+	jmp	[ss:shiftdrawtable+si]	;procedure to draw this width
+
+;
+; one byte character
+;
+shift1wide:
+	dec	dx
+EVEN
+@@loop1:
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+	loop	@@loop1
+	ret
+
+;
+; two byte character
+;
+shift2wide:
+	dec	dx
+	dec	dx
+EVEN
+@@loop2:
+	SHIFTNOXOR
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+	loop	@@loop2
+	ret
+
+;
+; three byte character
+;
+shift3wide:
+	sub	dx,3
+EVEN
+@@loop3:
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+	loop	@@loop3
+	ret
+
+;
+; four byte character
+;
+shift4wide:
+	sub	dx,4
+EVEN
+@@loop4:
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+	loop	@@loop4
+	ret
+
+;
+; five byte character
+;
+shift5wide:
+	sub	dx,5
+EVEN
+@@loop5:
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+	loop	@@loop5
+	ret
+
+
+
+ENDP
+
+;============================================================================
+
+;==================
+;
+; VW_DrawPropString
+;
+; Draws a C string of characters at px/py and advances px
+;
+; Assumes write mode 0
+;
+;==================
+
+CODESEG
+
+PROC	VW_DrawPropString	string:DWORD
+PUBLIC	VW_DrawPropString
+USES	SI,DI
+
+;
+; proportional spaceing, which clears the buffer ahead of it, so only
+; clear the first collumn
+;
+	mov	al,0
+line	=	0
+REPT	BUFFHEIGHT
+	mov	[BYTE databuffer+BUFFWIDTH*line],al
+line	=	line+1
+ENDM
+
+;
+; shift the characters into the buffer
+;
+@@shiftchars:
+	mov	ax,[px]
+	and	ax,7
+	mov	[bufferbit],ax
+	mov	[bufferbyte],0
+
+	mov	ax,[WORD string]
+	mov	[stringptr],ax
+	mov	ax,[WORD string+2]
+	mov	[stringptr+2],ax
+
+@@shiftone:
+	mov	es,[stringptr+2]
+	mov	bx,[stringptr]
+	inc	[stringptr]
+	mov	bx,[es:bx]
+	xor	bh,bh
+	or	bl,bl
+	jz	@@allshifted
+	call	ShiftPropChar
+	jmp	@@shiftone
+
+@@allshifted:
+;
+; calculate position to draw buffer on screen
+;
+	mov	bx,[py]
+	shl	bx,1
+	mov	di,[ylookup+bx]
+	add	di,[bufferofs]
+	add	di,[panadjust]
+
+	mov	ax,[px]
+	shr	ax,1
+	shr	ax,1
+	shr	ax,1		;x location in bytes
+	add	di,ax
+	mov	[screenspot],di
+
+;
+; advance px
+;
+	mov	ax,[bufferbyte]
+	shl	ax,1
+	shl	ax,1
+	shl	ax,1
+	or	ax,[bufferbit]
+	add	[px],ax
+
+;
+; draw it
+;
+
+; set xor/or mode
+	mov	dx,GC_INDEX
+	mov	al,GC_DATAROTATE
+	mov	ah,[pdrawmode]
+	WORDOUT
+
+; set mapmask to color
+	mov	dx,SC_INDEX
+	mov	al,SC_MAPMASK
+	mov	ah,[fontcolor]
+	WORDOUT
+
+	mov	ax,[bufferbyte]
+	test	[bufferbit],7
+	jz	@@go
+	inc	ax				;so the partial byte also gets drawn
+@@go:
+	mov	[bufferwidth],ax
+	mov	si,[fontnumber]
+	shl	si,1
+	mov	es,[grsegs+STARTFONT*2+si]
+	mov	ax,[es:pcharheight]
+	mov	[bufferheight],ax
+
+	mov	si,OFFSET databuffer
+	call	BufferToScreen
+
+; set copy mode
+	mov	dx,GC_INDEX
+	mov	ax,GC_DATAROTATE
+	WORDOUT
+
+; set mapmask to all
+	mov	dx,SC_INDEX
+	mov	ax,SC_MAPMASK + 15*256
+	WORDOUT
+
+
+	ret
+
+ENDP
+
+endif	;numfont
+
+;============================================================================
+;
+; MASKED FONT DRAWING ROUTINES
+;
+;============================================================================
+
+if	numfontm
+
+DATASEG
+
+mshiftdrawtable	dw      0,mshift1wide,mshift2wide,mshift3wide
+
+
+CODESEG
+
+;==================
+;
+; ShiftMPropChar
+;
+; Call with BX = character number (0-255)
+; Draws one character to the buffer at bufferbyte/bufferbit, and adjusts
+; them to the new position
+;
+;==================
+
+PROC	ShiftMPropChar	NEAR
+
+	mov	si,[fontnumber]
+	shl	si,1
+	mov	es,[grsegs+STARTFONTM*2+si]	;segment of font to use
+
+;
+; find character location, width, and height
+;
+	mov	si,[es:charwidth+bx]
+	and	si,0ffh					;SI hold width in pixels
+	shl	bx,1
+	mov	bx,[es:charloc+bx]		;BX holds pointer to character data
+
+;
+; look up which shift table to use, based on bufferbit
+;
+	mov	di,[bufferbit]
+	shl	di,1
+	mov	bp,[shifttabletable+di]	;BP holds pointer to shift table
+
+	mov	di,OFFSET databuffer
+	add	di,[bufferbyte]			;DI holds pointer to buffer
+
+	mov	cx,[bufferbit]
+	add	cx,si					;new bit position
+	mov	ax,cx
+	and	ax,7
+	mov	[bufferbit],ax			;new bit position
+	mov	ax,cx
+	shr	ax,1
+	shr	ax,1
+	shr	ax,1
+	add	[bufferbyte],ax			;new byte position
+
+	add	si,7
+	shr	si,1
+	shr	si,1
+	shr	si,1					;bytes the character is wide
+	shl	si,1                    ;*2 to look up in shiftdrawtable
+
+	mov	cx,[es:pcharheight]
+	mov	dx,BUFFWIDTH
+	jmp	[ss:mshiftdrawtable+si]	;procedure to draw this width
+
+;
+; one byte character
+;
+mshift1wide:
+	dec	dx
+
+EVEN
+@@loop1m:
+	SHIFTWITHXOR
+	add	di,dx			; next line in buffer
+
+	loop	@@loop1m
+
+	mov	cx,[es:pcharheight]
+
+EVEN
+@@loop1:
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+	loop	@@loop1
+
+	ret
+
+;
+; two byte character
+;
+mshift2wide:
+	dec	dx
+	dec	dx
+EVEN
+@@loop2m:
+	SHIFTWITHXOR
+	SHIFTWITHXOR
+	add	di,dx			; next line in buffer
+
+	loop	@@loop2m
+
+	mov	cx,[es:pcharheight]
+
+EVEN
+@@loop2:
+	SHIFTNOXOR
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+	loop	@@loop2
+
+	ret
+
+;
+; three byte character
+;
+mshift3wide:
+	sub	dx,3
+EVEN
+@@loop3m:
+	SHIFTWITHXOR
+	SHIFTWITHXOR
+	SHIFTWITHXOR
+	add	di,dx			; next line in buffer
+
+	loop	@@loop3m
+
+	mov	cx,[es:pcharheight]
+
+EVEN
+@@loop3:
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+	loop	@@loop3
+
+	ret
+
+
+ENDP
+
+;============================================================================
+
+;==================
+;
+; VW_DrawMPropString
+;
+; Draws a C string of characters at px/py and advances px
+;
+; Assumes write mode 0
+;
+;==================
+
+
+
+PROC	VW_DrawMPropString	string:DWORD
+PUBLIC	VW_DrawMPropString
+USES	SI,DI
+
+;
+; clear out the first byte of the buffer, the rest will automatically be
+; cleared as characters are drawn into it
+;
+	mov	si,[fontnumber]
+	shl	si,1
+	mov	es,[grsegs+STARTFONTM*2+si]
+	mov	dx,[es:pcharheight]
+	mov	di,OFFSET databuffer
+	mov	ax,ds
+	mov	es,ax
+	mov	bx,BUFFWIDTH-1
+
+	mov	cx,dx
+	mov	al,0ffh
+@@maskfill:
+	stosb				; fill the mask part with $ff
+	add	di,bx
+	loop	@@maskfill
+
+	mov	cx,dx
+	xor	al,al
+@@datafill:
+	stosb				; fill the data part with $0
+	add	di,bx
+	loop	@@datafill
+
+;
+; shift the characters into the buffer
+;
+	mov	ax,[px]
+	and	ax,7
+	mov	[bufferbit],ax
+	mov	[bufferbyte],0
+
+	mov	ax,[WORD string]
+	mov	[stringptr],ax
+	mov	ax,[WORD string+2]
+	mov	[stringptr+2],ax
+
+@@shiftone:
+	mov	es,[stringptr+2]
+	mov	bx,[stringptr]
+	inc	[stringptr]
+	mov	bx,[es:bx]
+	xor	bh,bh
+	or	bl,bl
+	jz	@@allshifted
+	call	ShiftMPropChar
+	jmp	@@shiftone
+
+@@allshifted:
+;
+; calculate position to draw buffer on screen
+;
+	mov	bx,[py]
+	shl	bx,1
+	mov	di,[ylookup+bx]
+	add	di,[bufferofs]
+	add	di,[panadjust]
+
+	mov	ax,[px]
+	shr	ax,1
+	shr	ax,1
+	shr	ax,1		;x location in bytes
+	add	di,ax
+	mov	[screenspot],di
+
+;
+; advance px
+;
+	mov	ax,[bufferbyte]
+	shl	ax,1
+	shl	ax,1
+	shl	ax,1
+	or	ax,[bufferbit]
+	add	[px],ax
+
+;
+; draw it
+;
+	mov	ax,[bufferbyte]
+	test	[bufferbit],7
+	jz	@@go
+	inc	ax				;so the partial byte also gets drawn
+@@go:
+	mov	[bufferwidth],ax
+	mov	es,[grsegs+STARTFONTM*2]
+	mov	ax,[es:pcharheight]
+	mov	[bufferheight],ax
+
+; set AND mode to punch out the mask
+	mov	dx,GC_INDEX
+	mov	ax,GC_DATAROTATE + 8*256
+	WORDOUT
+
+; set mapmask to all
+	mov	dx,SC_INDEX
+	mov	ax,SC_MAPMASK + 15*256
+	WORDOUT
+
+	mov	si,OFFSET databuffer
+	call	BufferToScreen
+
+; set OR mode to fill in the color
+	mov	dx,GC_INDEX
+	mov	ax,GC_DATAROTATE + 16*256
+	WORDOUT
+
+; set mapmask to color
+	mov	dx,SC_INDEX
+	mov	al,SC_MAPMASK
+	mov	ah,[fontcolor]
+	WORDOUT
+
+	call	BufferToScreen		; SI is still in the right position in buffer
+
+; set copy mode
+	mov	dx,GC_INDEX
+	mov	ax,GC_DATAROTATE
+	WORDOUT
+
+; set mapmask to all
+	mov	dx,SC_INDEX
+	mov	ax,SC_MAPMASK + 15*256
+	WORDOUT
+
+
+	ret
+
+ENDP
+
+endif		; if numfontm
+
+endif		; if fonts
diff --git a/16/keen456/KEEN4-6/CK_DEF.H b/16/keen456/KEEN4-6/CK_DEF.H
new file mode 100755
index 00000000..62e79445
--- /dev/null
+++ b/16/keen456/KEEN4-6/CK_DEF.H
@@ -0,0 +1,775 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+#ifndef __CK_DEF__
+#define __CK_DEF__
+
+#include <BIOS.H>
+#include <CONIO.H>
+
+#include "ID_HEADS.H"
+
+/*
+=============================================================================
+
+						 GLOBAL CONSTANTS & MACROS
+
+=============================================================================
+*/
+
+#define MAXACTORS 100
+
+#define GAMELEVELS 25
+
+#define CONVERT_GLOBAL_TO_TILE(x)  ((x)>>(G_T_SHIFT))
+#define CONVERT_TILE_TO_GLOBAL(x)  ((x)<<(G_T_SHIFT))
+#define CONVERT_GLOBAL_TO_PIXEL(x) ((x)>>(G_P_SHIFT))
+#define CONVERT_PIXEL_TO_GLOBAL(x) ((x)<<(G_P_SHIFT))
+#define CONVERT_PIXEL_TO_TILE(x)   ((x)>>(P_T_SHIFT))
+#define CONVERT_TILE_TO_PIXEL(x)   ((x)<<(P_T_SHIFT))
+
+#define SPAWN_ADJUST_Y(y, h) (CONVERT_TILE_TO_GLOBAL(y) + (CONVERT_PIXEL_TO_GLOBAL(16-(h))))
+
+#define ARRAYLENGTH(x) (sizeof(x)/sizeof(*(x)))
+
+#define CA_UnmarkGrChunk(num) (grneeded[num] &= ~ca_levelbit)
+
+#define SetPalette(pal) {_ES=FP_SEG(pal); _DX=FP_OFF(pal); _AX=0x1002; geninterrupt(0x10);}
+#define SetPaletteEx(pal) {(pal)[16] = bordercolor; SetPalette(pal);}
+
+//HACK IMPORTS:
+void RFL_InitAnimList(void);
+void CA_FreeGraphics(void);
+void CA_SetGrPurge(void);
+
+/*
+Note:
+
+The ID software memory manager doesn't care about the different purge levels.
+Using PURGE_FIST is identical to using PURGE_LAST.
+*/
+#define PURGE_FIRST 3
+#define PURGE_LAST 1
+
+#define PLATFORMBLOCK 31
+#define DIRARROWSTART 91
+#define DIRARROWEND   (DIRARROWSTART+arrow_None)
+
+/*
+=============================================================================
+
+						   GLOBAL TYPES
+
+=============================================================================
+*/
+
+//SDL-style integer types - just to make future SDL ports easier
+typedef unsigned int Uint16;
+typedef signed int Sint16;
+typedef unsigned char Uint8;
+typedef signed char Sint8;
+typedef unsigned long Uint32;
+typedef signed long Sint32;
+//Note: only the game code (CK_*.C, K?_*.C) uses these!
+
+//some compile-time checks to make sure the ints have the correct size
+#if (sizeof(Uint16) != 2)
+#error 'Uint16' has wrong size
+#elif (sizeof(Sint16) != 2)
+#error 'Sint16' has wrong size
+#elif (sizeof(Uint8) != 1)
+#error 'Uint8' has wrong size
+#elif (sizeof(Sint8) != 1)
+#error 'Sint8' has wrong size
+#elif (sizeof(Uint32) != 4)
+#error 'Uint32' has wrong size
+#elif (sizeof(Sint32) != 4)
+#error 'Sint32' has wrong size
+#endif
+
+typedef enum {
+	arrow_North,     // 0
+	arrow_East,      // 1
+	arrow_South,     // 2
+	arrow_West,      // 3
+	arrow_NorthEast, // 4
+	arrow_SouthEast, // 5
+	arrow_SouthWest, // 6
+	arrow_NorthWest, // 7
+	arrow_None       // 8
+} arrowdirtype;
+
+typedef enum {
+	ex_stillplaying, //  0
+	ex_died,         //  1
+	ex_completed,    //  2
+	ex_rescued,      //  3, only in Keen 4
+	ex_warped,       //  4
+	ex_resetgame,    //  5
+	ex_loadedgame,   //  6
+	ex_foot,         //  7, only in Keen 4
+	ex_abortgame,    //  8
+	ex_sandwich,     //  9, only in Keen 6
+	ex_hook,         // 10, only in Keen 6
+	ex_card,         // 11, only in Keen 6
+	ex_molly,        // 12, only in Keen 6
+	ex_portout,      // 13, only in Keen 5
+	ex_fusebroke,    // 14, only in Keen 5
+	ex_qedbroke,     // 15, only in Keen 5
+	NUMEXITTYPES
+} exittype;
+
+typedef enum
+{
+	INTILE_NOTHING,        //  0
+	INTILE_POLE,           //  1
+	INTILE_DOOR,           //  2
+	INTILE_DEADLY,         //  3
+	INTILE_DROP,           //  4
+	INTILE_SWITCH0,        //  5
+	INTILE_SWITCH1,        //  6
+	INTILE_GEMSOCKET0,     //  7
+	INTILE_GEMSOCKET1,     //  8
+	INTILE_GEMSOCKET2,     //  9
+	INTILE_GEMSOCKET3,     // 10
+	INTILE_SHORESOUTH,     // 11
+	INTILE_SHOREWEST,      // 12
+	INTILE_SHORENORTH,     // 13
+	INTILE_SHOREEAST,      // 14
+	INTILE_BRIDGESWITCH,   // 15
+	INTILE_MOON,           // 16
+	INTILE_DIRARROW,       // 17 (not used in the code, but assigned to tiles in Keen 5 & 6)
+	INTILE_BRIDGE,         // 18
+	INTILE_FORCEFIELD,     // 19
+	INTILE_TELEPORT,       // 20
+	INTILE_BONUS100,       // 21
+	INTILE_BONUS200,       // 22
+	INTILE_BONUS500,       // 23
+	INTILE_BONUS1000,      // 24
+	INTILE_BONUS2000,      // 25
+	INTILE_BONUS5000,      // 26
+	INTILE_EXTRALIFE,      // 27
+	INTILE_AMMO,           // 28
+	INTILE_29,             // 29 (never used)
+	INTILE_FORCEFIELDEND,  // 30
+	INTILE_AMPTONCOMPUTER, // 31
+	INTILE_KEYCARDDOOR,    // 32
+	INTILE_ELEVATORLEFT,   // 33
+	INTILE_ELEVATORRIGHT,  // 34
+
+	INTILE_FOREGROUND = 0x80
+} intiletype;
+
+#define INTILE_TYPEMASK (INTILE_FOREGROUND-1)
+
+typedef enum
+{
+	nothing,         //  0
+	inertobj,        //  1
+	keenobj,         //  2
+	stunshotobj,     //  3
+#if defined KEEN4
+	bonusobj,        //  4
+	slugobj,         //  5
+	oracleobj,       //  6
+	classtype_7,     //  7, never used
+	eggobj,          //  8
+	madmushroomobj,  //  9
+	arachnutobj,     // 10
+	skypestobj,      // 11
+	wormouthobj,     // 12
+	thundercloudobj, // 13
+	berkeloidobj,    // 14
+	bounderobj,      // 15
+	inchwormobj,     // 16
+	footobj,         // 17
+	lickobj,         // 18
+	mimrockobj,      // 19
+	platformobj,     // 20
+	dopefishobj,     // 21
+	schoolfishobj,   // 22
+	pixieobj,        // 23
+	lindseyobj,      // 24
+	lightningobj,    // 25
+	treasureeaterobj,// 26
+	eggbirdobj,      // 27
+	classtype_28,    // 28, never used
+	classtype_29,    // 29, never used
+	scubaobj,        // 30
+	mshotobj,        // 31
+	mineobj,         // 32
+	stunnedobj,      // 33
+	flagobj,         // 34
+#elif defined KEEN5
+	mshotobj,        //  4
+	bonusobj,        //  5
+	platformobj,     //  6
+	stunnedobj,      //  7
+	flagobj,         //  8
+	sparkyobj,       //  9
+	mineobj,         // 10
+	slicestarobj,    // 11
+	roboredobj,      // 12
+	spirogripobj,    // 13
+	amptonobj,       // 14
+	cannonobj,       // 15
+	volteobj,        // 16
+	shelleyobj,      // 17, never used
+	spindredobj,     // 18
+	shikadimasterobj,// 19
+	shikadiobj,      // 20
+	petobj,          // 21
+	spherefulobj,    // 22
+	scottieobj,      // 23
+	teleporterobj,   // 24
+	qedobj,          // 25
+#elif defined KEEN6
+	mshotobj,        //  4
+	bonusobj,        //  5
+	platformobj,     //  6
+	bloogobj,        //  7
+	bloogletobj,     //  8
+	classtype_9,     //  9, never used
+	fleexobj,        // 10
+	classtype_11,    // 11, never used
+	mollyobj,        // 12
+	babobbaobj,      // 13
+	bobbaobj,        // 14
+	classtype_15,    // 15
+	nospikeobj,      // 16
+	gikobj,          // 17
+	cannonobj,       // 18
+	orbatrixobj,     // 19
+	bipobj,          // 20
+	flectobj,        // 21
+	blorbobj,        // 22
+	ceilickobj,      // 23
+	blooguardobj,    // 24
+	stunnedobj,      // 25
+	bipshipobj,      // 26
+	sandwichobj,     // 27
+	hookobj,         // 28
+	passcardobj,     // 29
+	grabbiterobj,    // 30
+	rocketobj,       // 31
+	grapplespotobj,  // 32
+	satelliteobj,    // 33
+	satellitestopobj,// 34
+	flagobj,         // 35
+#endif
+	NUMCLASSTYPES
+} classtype;
+
+typedef struct statestruct
+{
+	Sint16 leftshapenum, rightshapenum;
+	enum {step,slide,think,stepthink,slidethink} progress;
+	boolean skippable;
+	boolean pushtofloor;
+	Sint16 tictime;
+	Sint16 xmove;
+	Sint16 ymove;
+	void (*think) (struct objstruct*);
+	void (*contact) (struct objstruct*, struct objstruct*);
+	void (*react) (struct objstruct*);
+	struct statestruct *nextstate;
+} statetype;
+
+typedef struct objstruct
+{
+	classtype obclass;
+	enum {ac_no, ac_yes, ac_allways, ac_removable} active;
+	boolean needtoreact;
+	enum {cl_noclip, cl_midclip, cl_fullclip} needtoclip;
+	Uint16 nothink;
+	Uint16 x, y;
+	Sint16 xdir, ydir;
+	Sint16 xmove, ymove;
+	Sint16 xspeed, yspeed;
+	Sint16 ticcount;
+	statetype *state;
+	Uint16 shapenum;
+	Uint16 priority;
+	Uint16 left, top, right, bottom, midx;
+	Uint16 tileleft, tiletop, tileright, tilebottom, tilemidx;
+	Sint16 hitnorth, hiteast, hitsouth, hitwest;
+	Sint16 temp1, temp2, temp3, temp4;
+	void *sprite;
+	struct objstruct *next, *prev;
+} objtype;
+
+typedef struct
+{
+	Uint16 worldx, worldy;
+	boolean leveldone[GAMELEVELS];
+	Sint32 score, nextextra;
+	Sint16 ammo, drops;
+#if defined KEEN4
+	Sint16 wetsuit;
+	Sint16 rescued;
+#elif defined KEEN5
+	boolean keycard;
+	Sint16 destroyed;	// never used
+	Sint16 numfuses;
+#elif defined KEEN6
+	Sint16 sandwichstate, hookstate, passcardstate, rocketstate;
+#endif
+	Sint16 keys[4];
+	Sint16 mapon;
+	Sint16 lives;
+	Sint16 difficulty;
+	objtype *riding;
+} gametype;
+
+/*
+=============================================================================
+
+						CK_MAIN DEFINITIONS
+
+=============================================================================
+*/
+
+extern char str[80], str2[20];
+extern boolean storedemo;
+
+void SizeText(char *text, Uint16 *width, Uint16 *height);
+
+/*
+=============================================================================
+
+						CK_DEMO DEFINITIONS
+
+=============================================================================
+*/
+
+extern boolean scorescreenkludge;
+
+void CheckLastScan(void);
+#if GRMODE == EGAGR
+void Terminator(void);
+void StarWars(void);
+#endif
+void ShowTitle(void);
+#if GRMODE == CGAGR
+void ShowCredits(void);
+#endif
+void RunDemo(Sint16 num);
+void DrawHighScores(void);
+void CheckHighScore(Sint32 score, Sint16 completed);
+void ShowHighScores(void);
+
+/*
+=============================================================================
+
+						CK_GAME DEFINITIONS
+
+=============================================================================
+*/
+
+void FreeGraphics(void);
+void NewGame(void);
+boolean SaveTheGame(Sint16 handle);
+boolean LoadTheGame(Sint16 handle);
+void ResetGame(void);
+void SetupGameLevel(boolean loadnow);
+void DialogDraw(char *title, Uint16 numcache);
+void DialogUpdate(void);
+void DialogFinish(void);
+void StartDemoRecord(void);
+void EndDemoRecord(void);
+void GameLoop(void);
+void HandleDeath(void);
+
+/*
+=============================================================================
+
+						CK_PLAY DEFINITIONS
+
+=============================================================================
+*/
+
+extern boolean singlestep, jumpcheat, godmode, keenkilled;
+extern exittype playstate;
+extern gametype gamestate;
+extern objtype *new, *check, *player, *scoreobj;
+extern Uint16 originxtilemax, originytilemax;
+extern ControlInfo c;
+extern boolean button2, button3;	// never used
+extern objtype dummyobj;
+extern Sint16 invincible;
+extern boolean oldshooting, showscorebox, joypad;
+extern Sint16 groundslam;
+extern boolean debugok;
+extern boolean jumpbutton, jumpheld, pogobutton, pogoheld, firebutton, fireheld, upheld;
+
+
+void CheckKeys(void);
+void StatusWindow(void);
+void CenterActor(objtype *ob);
+void WorldScrollScreen(objtype *ob);
+void ScrollScreen(objtype *ob);
+void InitObjArray(void);
+Sint16 GetNewObj(boolean usedummy);
+void RemoveObj(objtype *ob);
+void GivePoints(Uint16 points);
+void StopMusic(void);
+void StartMusic(Uint16 num);
+void PlayLoop(void);
+
+/*
+=============================================================================
+
+						CK_TEXT DEFINITIONS
+
+=============================================================================
+*/
+
+void HelpScreens(void);
+void FinaleLayout(void);
+
+/*
+=============================================================================
+
+						CK_STATE DEFINITIONS
+
+=============================================================================
+*/
+
+extern Sint16 wallclip[8][16];
+
+extern Sint16 xtry;
+extern Sint16 ytry;
+extern boolean playerkludgeclipcancel;
+
+void MoveObjVert(objtype *ob, Sint16 ymove);
+void MoveObjHoriz(objtype *ob, Sint16 xmove);
+void PlayerBottomKludge(objtype *ob);
+void PlayerTopKludge(objtype *ob);
+void ClipToEnds(objtype *ob);
+void ClipToSides(objtype *ob);
+boolean CheckPosition(objtype *ob);
+boolean StatePositionOk(objtype *ob, statetype *state);
+
+#ifdef KEEN5
+void CalcBounds(objtype *ob);
+#endif
+
+void ClipToWalls(objtype *ob);
+void FullClipToWalls(objtype *ob);
+void PushObj(objtype *ob);
+void ClipToSpriteSide(objtype *push, objtype *solid);
+void ClipToSpriteTop(objtype *push, objtype *solid);
+void ClipToSprite(objtype *push, objtype *solid, boolean squish);
+Sint16 DoActor(objtype *ob, Sint16 numtics);
+void StateMachine(objtype *ob);
+void NewState(objtype *ob, statetype *state);
+void ChangeState(objtype *ob, statetype *state);
+boolean OnScreen(objtype *ob);
+void DoGravity(objtype *ob);
+void DoWeakGravity(objtype *ob);
+void DoTinyGravity(objtype *ob);
+void AccelerateX(objtype *ob, Sint16 dir, Sint16 maxspeed);
+void AccelerateXv(objtype *ob, Sint16 dir, Sint16 maxspeed);
+void AccelerateY(objtype *ob, Sint16 dir, Sint16 maxspeed);
+void FrictionX(objtype *ob);
+void FrictionY(objtype *ob);
+void StunObj(objtype *ob, objtype *shot, statetype *stunstate);
+void T_Projectile(objtype *ob);
+void T_WeakProjectile(objtype *ob);
+void ProjectileThink1(objtype *ob);
+void T_Velocity(objtype *ob);
+void SetReactThink(objtype *ob);
+void T_Stunned(objtype *ob);
+void C_Lethal(objtype *ob, objtype *hit);
+void R_Draw(objtype *ob);
+void R_Walk(objtype *ob);
+void R_WalkNormal(objtype *ob);
+void BadState(void);
+void R_Stunned(objtype *ob);
+
+extern statetype sc_deadstate;
+extern statetype sc_badstate;
+
+/*
+=============================================================================
+
+						CK_KEEN DEFINITIONS
+
+=============================================================================
+*/
+
+extern Uint16 bounceangle[8][8];
+#ifndef KEEN4
+extern arrowdirtype arrowflip[];
+#endif
+
+extern statetype s_keenstand;
+extern statetype s_keenpauselook;
+extern statetype s_keenwait1;
+extern statetype s_keenwait2;
+extern statetype s_keenwait3;
+extern statetype s_keenwait4;
+extern statetype s_keenwait5;
+extern statetype s_keenwait6;
+extern statetype s_keenmoon1;
+extern statetype s_keenmoon2;
+extern statetype s_keenmoon3;
+extern statetype s_keenread;
+extern statetype s_keenread2;
+extern statetype s_keenread3;
+extern statetype s_keenread4;
+extern statetype s_keenread5;
+extern statetype s_keenread6;
+extern statetype s_keenread7;
+extern statetype s_keenstopread;
+extern statetype s_keenstopread2;
+extern statetype s_keenstopread3;
+extern statetype s_keenlookup;
+extern statetype s_keenlookup2;
+extern statetype s_keenlookdown;
+extern statetype s_keenlookdown2;
+extern statetype s_keenlookdown3;
+extern statetype s_keenlookdown4;
+extern statetype s_keendrop;
+extern statetype s_keendead;
+extern statetype s_keendie1;
+extern statetype s_keendie2;
+#ifdef KEEN4
+extern statetype s_keensuitdie1;
+extern statetype s_keensuitdie2;
+#endif
+extern statetype s_keenshoot1;
+extern statetype s_keenshoot2;
+extern statetype s_keenshootup1;
+extern statetype s_keenshootup2;
+extern statetype s_keenswitch;
+extern statetype s_keenswitch2;
+extern statetype s_keenkey;
+extern statetype s_keenlineup;
+extern statetype s_keenenter1;
+extern statetype s_keenenter2;
+extern statetype s_keenenter3;
+extern statetype s_keenenter4;
+extern statetype s_keenenter5;
+extern statetype s_keenpole;
+extern statetype s_keenclimb1;
+extern statetype s_keenclimb2;
+extern statetype s_keenclimb3;
+extern statetype s_keenslide1;
+extern statetype s_keenslide2;
+extern statetype s_keenslide3;
+extern statetype s_keenslide4;
+extern statetype s_keenpoleshoot1;
+extern statetype s_keenpoleshoot2;
+extern statetype s_keenpoleshootup1;
+extern statetype s_keenpoleshootup2;
+extern statetype s_keenpoleshootdown1;
+extern statetype s_keenpoleshootdown2;
+extern statetype s_keenwalk1;
+extern statetype s_keenwalk2;
+extern statetype s_keenwalk3;
+extern statetype s_keenwalk4;
+extern statetype s_keenpogodown;
+extern statetype s_keenpogo;
+extern statetype s_keenpogo2;
+extern statetype s_keenjump1;
+extern statetype s_keenjump2;
+extern statetype s_keenjump3;
+extern statetype s_keenjump4;
+extern statetype s_keenairshoot1;
+extern statetype s_keenairshoot2;
+extern statetype s_keenairshoot3;
+extern statetype s_keenairshootup1;
+extern statetype s_keenairshootup2;
+extern statetype s_keenairshootup3;
+extern statetype s_keenairshootdown1;
+extern statetype s_keenairshootdown2;
+extern statetype s_keenairshootdown3;
+extern statetype s_keenholdon;
+extern statetype s_keenholdon2;
+extern statetype s_keenclimbup;
+extern statetype s_keenclimbup2;
+extern statetype s_keenclimbup3;
+extern statetype s_keenclimbup4;
+extern statetype s_keenclimbup5;
+
+extern Sint16 slopespeed[8];
+extern Sint16 polexspeed[3];
+
+extern Sint16 shotsinclip[4];
+extern Sint16 bonussound[];
+extern Sint16 bonuspoints[];
+extern Sint16 bonussprite[];
+
+extern Uint16 zeromap;
+
+extern Sint16 singlegravity;
+extern Sint16 jumptime;
+extern Sint32 leavepoletime;
+extern Sint16 moonok;
+
+void SpawnKeen(Sint16 x, Sint16 y, Sint16 dir);
+boolean CheckGrabPole(objtype *ob);
+boolean CheckEnterHouse(objtype *ob);
+void WalkSound1(objtype *ob);
+void WalkSound2(objtype *ob);
+void KeenStandThink(objtype *ob);
+void KeenPauseThink(objtype *ob);
+void KeenReadThink(objtype *ob);
+void KeenLookUpThink(objtype *ob);
+void KeenLookDownThink(objtype *ob);
+void KeenWalkThink(objtype *ob);
+void T_LineUp(objtype *ob);
+void KeenEnterThink(objtype *ob);
+void KeenSwitchThink(objtype *ob);
+void KeenKeyThink(objtype *ob);
+void KeenAirThink(objtype *ob);
+void KeenBounceThink(objtype *ob);
+void KeenPogoThink(objtype *ob);
+void PoleActions(objtype *ob);
+void KeenPoleThink(objtype *ob);
+void KeenClimbThink(objtype *ob);
+void KeenDropThink(objtype *ob);
+void KeenDropDownThink(objtype *ob);
+void KeenHoldThink(objtype *ob);
+void KeenShootThink(objtype *ob);
+void T_PullUp1(objtype *ob);
+void T_PullUp2(objtype *ob);
+void T_PullUp3(objtype *ob);
+void T_PulledUp(objtype *ob);
+void KeenDieThink(objtype *ob);
+void KillKeen(void);
+void KeenContact(objtype *ob, objtype *hit);
+void KeenPosContact(objtype *ob, objtype *hit);
+void HandleRiding(objtype *ob);
+void TileBonus(Uint16 x, Uint16 y, Uint16 bonus);
+void GiveDrop(Uint16 x, Uint16 y);
+void CheckInTiles(objtype *ob);
+void KeenSimpleReact(objtype *ob);
+void KeenStandReact(objtype *ob);
+void KeenWalkReact(objtype *ob);
+void KeenAirReact(objtype *ob);
+void KeenPogoReact(objtype *ob);
+void KeenPoleReact(objtype *ob);
+
+
+/*
+=============================================================================
+
+						CK_KEEN2 DEFINITIONS
+
+=============================================================================
+*/
+
+extern statetype s_score;
+extern statetype s_demo;
+void SpawnScore(void);
+void UpdateScore(objtype *ob);
+void DrawDemoPlaque(objtype *ob);
+
+extern statetype s_worldkeen;
+extern statetype s_worldkeenwave1;
+extern statetype s_worldkeenwave2;
+extern statetype s_worldkeenwave3;
+extern statetype s_worldkeenwave4;
+extern statetype s_worldkeenwave5;
+extern statetype s_worldkeenwalk;
+void SpawnWorldKeen(Sint16 x, Sint16 y);
+#ifdef KEEN5
+void SpawnWorldKeenPort(Uint16 tileX, Uint16 tileY);
+#endif
+void CheckEnterLevel(objtype *ob);
+void T_KeenWorld(objtype *ob);
+void T_KeenWorldWalk(objtype *ob);
+void CheckWorldInTiles(objtype *ob);
+
+#ifdef KEEN4
+extern statetype s_keenonfoot1;
+extern statetype s_keenonfoot2;
+extern statetype s_worldswim;
+void T_FootFly(objtype *ob);
+void T_KeenWorldSwim(objtype *ob);
+#endif
+
+#ifdef KEEN5
+extern statetype s_worldelevate;
+void T_Elevate(objtype *ob);
+#endif
+
+extern statetype s_flagwave1;
+extern statetype s_flagwave2;
+extern statetype s_flagwave3;
+extern statetype s_flagwave4;
+void SpawnFlag(Sint16 x, Sint16 y);
+
+#ifndef KEEN5
+extern statetype s_throwflag0;
+extern statetype s_throwflag1;
+extern statetype s_throwflag2;
+extern statetype s_throwflag3;
+extern statetype s_throwflag4;
+extern statetype s_throwflag5;
+extern statetype s_throwflag6;
+void SpawnThrowFlag(Sint16 x, Sint16 y);
+void TossThink(objtype *ob);
+void PathThink(objtype *ob);
+void FlagAlign(objtype *ob);
+#endif
+
+extern statetype s_stunray1;
+extern statetype s_stunray2;
+extern statetype s_stunray3;
+extern statetype s_stunray4;
+extern statetype s_stunhit;
+extern statetype s_stunhit2;
+void SpawnShot(Uint16 x, Uint16 y, Direction dir);
+void ExplodeShot(objtype *ob);
+void T_Shot(objtype *ob);
+void R_Shot(objtype *ob);
+
+extern statetype s_door1;
+extern statetype s_door2;
+extern statetype s_door3;
+void DoorOpen(objtype *ob);
+
+#ifdef KEEN5
+extern statetype s_carddoor;
+void CardDoorOpen(objtype *ob);
+#endif
+
+/*
+=============================================================================
+
+						OTHER DEFINITIONS
+
+=============================================================================
+*/
+
+#if defined KEEN4
+#include "K4_DEF.H"
+#elif defined KEEN5
+#include "K5_DEF.H"
+#elif defined KEEN6
+#include "K6_DEF.H"
+#endif
+
+#endif
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/CK_DEMO.C b/16/keen456/KEEN4-6/CK_DEMO.C
new file mode 100755
index 00000000..5004cf34
--- /dev/null
+++ b/16/keen456/KEEN4-6/CK_DEMO.C
@@ -0,0 +1,2132 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+#include "CK_DEF.H"
+
+/*
+=============================================================================
+
+						 GLOBAL VARIABLES
+
+=============================================================================
+*/
+
+boolean scorescreenkludge;
+
+/*
+=============================================================================
+
+						 LOCAL VARIABLES
+
+=============================================================================
+*/
+
+#if GRMODE == EGAGR
+
+Uint8 starcolors[17] = STARPALETTE;
+Uint16 plaquenum[4] = {IDSOFTPIC, PROGTEAMPIC, ARTISTPIC, DIRECTORPIC};
+Uint8 termcolors[17] = INTROPALETTE;
+Uint8 termcolors2[17] = SHRINKPALETTE;
+
+Uint8 ortoend[8] = {0xFF, 0x7F, 0x3F, 0x1F, 0x0F, 0x07, 0x03, 0x01};
+Uint8 andtoend[8] = {0x00, 0x80, 0xC0, 0xE0, 0xF0, 0xF8, 0xFC, 0xFE};
+
+/////////////////////////////////////////////////////////////////////////////
+// uninitialized variables:
+/////////////////////////////////////////////////////////////////////////////
+
+typedef struct {
+	Uint16 height;
+	Uint16 width;
+	Uint16 rowofs[200];
+} shapehead;
+
+typedef shapehead _seg * shapeseg;
+
+// text crawl variables:
+memptr linecode;
+void far *linestarts[200];
+Uint16 sourceline[200];
+Uint16 masterlines;
+void far *routine;
+memptr sourcepic;
+memptr bittables;
+
+// terminator intro variables:
+shapeseg commander;
+shapeseg keen;
+shapeseg both;
+memptr scaletable;
+memptr cmdrshifts[8];
+Sint16 commanderbwide;
+Uint16 lastsource;
+Uint16 keenstart;
+memptr basepl[5];
+Uint16 baseplwidth[5];
+Uint16 baseplheight[5];
+memptr plaqueseg;
+Uint16 plaquewidth;
+Uint16 plaquewidthwords;
+Uint16 plaqueheight;
+Uint16 plaqueplane;
+Uint16 plaquedelta;
+Uint16 *shiftptr;
+Uint16 planeon;
+Sint16 drawheight;
+Uint16 source2;
+static Uint16 t_dest;
+static Sint16 plaque;
+static Sint16 plaquephase;
+static Sint16 plaquey;
+static Sint16 lastframe;
+static Sint16 pageon;
+static Sint16 prevbottom[2];
+Uint16 pageofs;
+Uint16 byteadjust;
+
+#endif	// if GRMODE == EGAGR
+
+//===========================================================================
+
+/*
+============================
+=
+= CheckLastScan
+=
+============================
+*/
+
+void CheckLastScan(void)
+{
+	if (LastScan)
+	{
+		if (storedemo)
+		{
+			playstate = ex_resetgame;
+			restartgame = gd_Normal;
+			IN_ClearKeysDown();
+			NewGame();
+		}
+#ifndef KEEN6
+		else if (LastScan == sc_F1)
+		{
+			HelpScreens();
+		}
+#endif
+		else
+		{
+			US_ControlPanel();
+			if (restartgame)
+			{
+				playstate = ex_resetgame;
+			}
+			else if (loadedgame)
+			{
+				playstate = ex_loadedgame;
+			}
+		}
+	}
+}
+
+#if GRMODE == EGAGR
+/*
+=============================================================================
+
+							TERMINATOR INTRO
+
+=============================================================================
+*/
+
+/*
+============================
+=
+= LoadPlaque
+=
+============================
+*/
+
+void LoadPlaque(Sint16 index)
+{
+	Sint16 LocatePlaque(Sint16 elapsed);
+
+	Uint16 chunk, picnum, width, height, planesize, i;
+	Uint8 far *source;
+	Uint16 far *dest;
+
+	//
+	// cache the pic and get pic size
+	//
+	chunk = plaquenum[index];
+	CA_CacheGrChunk(chunk);
+	picnum = chunk - STARTPICS;
+	baseplwidth[index] = width = pictable[picnum].width;
+	baseplheight[index] = height = pictable[picnum].height;
+	planesize = width * height * 2;
+
+	//
+	// allocate buffer and convert pic into to our format
+	// (convert bytes to word indices for faster shift-drawing)
+	//
+	MM_GetPtr(&basepl[index], planesize*2);	// 2 planes
+	source = grsegs[chunk];
+	dest = basepl[index];
+	for (i=0; i<planesize; i++)
+	{
+		*dest++ = *source++ << 1;
+	}
+
+	//
+	// pic in original format is no longer needed
+	//
+	MM_FreePtr(&grsegs[chunk]);
+}
+
+/*
+============================
+=
+= DrawPlaque
+=
+============================
+*/
+
+void DrawPlaque(Sint16 elapsed, Uint16 x)
+{
+	Uint16 shift, xb;
+	Sint16 y, bottom, oldbottom;
+	Uint16 eraseheight, skip, screenoff;
+
+	shift = x & 7;
+	xb = (pageofs + (x / 8)) + (20 - (plaquewidth >> 1));
+
+	EGAMAPMASK(12);	// write to "red" and "intensity" plane (for erasing old pic)
+
+	//
+	// update position (and pic number)
+	//
+	y = LocatePlaque(elapsed);
+
+	//
+	// erase leftovers of the previous frame
+	//
+	bottom = y + plaqueheight;
+	if (bottom < 0)
+		bottom = 0;
+	oldbottom = prevbottom[pageon];
+	if (bottom < 200 && oldbottom > bottom)
+	{
+		eraseheight = oldbottom - bottom;
+		screenoff = xb + ylookup[bottom];
+		asm {
+			mov	es, screenseg;
+			mov	bx, linewidth;
+			sub	bx, plaquewidthwords;
+			sub	bx, plaquewidthwords;
+			mov	di, screenoff;
+			mov	dx, eraseheight;
+			mov	si, plaquewidthwords;
+			xor	ax, ax;
+		}
+eraseloop:
+		asm {
+			mov	cx, si;
+			rep stosw;
+			add	di, bx;
+			dec	dx;
+			jnz	eraseloop;
+		}
+	}
+	if (bottom > 200)
+		bottom = 200;
+	prevbottom[pageon] = bottom;
+
+	//
+	// draw the (new) pic at the new position
+	//
+	drawheight = plaqueheight;
+	skip = 0;
+	if (y < 0)
+	{
+		skip = -y * (plaquewidth << 1);
+		drawheight += y;
+		y = 0;
+	}
+	else if (y + plaqueheight > 200)
+	{
+		drawheight = 200 - y;
+	}
+	source2 = skip + plaqueplane;
+	if (drawheight > 0)
+	{
+		shiftptr = shifttabletable[shift];
+		t_dest = xb + ylookup[y];
+		asm {
+			mov	bx, skip;
+			push	bp;
+			mov	bp, shiftptr;
+			mov	es, screenseg;
+			mov	ds, plaqueseg;
+			mov	ah, 4;
+			mov	BYTE PTR ss:planeon, ah;
+		}
+planeloop:
+		asm {
+			mov	dx, SC_INDEX;
+			mov	al, SC_MAPMASK;
+			out	dx, ax;
+			mov	dx, ss:drawheight;
+			mov	di, ss:t_dest;
+		}
+yloop:
+		asm {
+			mov	cx, ss:plaquewidth;
+			xor	al, al;
+		}
+xloop:
+		asm {
+			mov	si, [bx];
+			add	bx, 2;
+			xor	ah, ah;
+			or 	ax, [bp+si];
+			stosb;
+			mov	al, ah;
+			loop	xloop;
+			stosb;
+			mov	WORD PTR es:[di], 0;
+			add	di, ss:plaquedelta;
+			dec	dx;
+			jnz	yloop;
+			mov	bx, ss:source2;
+			mov	ah, BYTE PTR ss:planeon;
+			shl	ah, 1;
+			mov	BYTE PTR ss:planeon, ah;
+			cmp	ah, 16;
+			jnz	planeloop;
+			pop	bp;
+			mov	ax, ss;
+			mov	ds, ax;
+		}
+	}
+}
+
+/*
+============================
+=
+= LocatePlaque
+=
+============================
+*/
+
+Sint16 LocatePlaque(Sint16 elapsed)
+{
+	switch (plaquephase)
+	{
+	case -1:
+		//
+		// pic starts to appear
+		//
+		plaqueseg = basepl[plaque];
+		plaquewidth = baseplwidth[plaque];
+		plaquewidthwords = (plaquewidth + 3) >> 1;
+		plaqueheight = baseplheight[plaque];
+		plaquedelta = linewidth - (plaquewidth + 1);
+		plaqueplane = (plaquewidth * plaqueheight) << 1;
+		plaquephase++;
+		lastframe = elapsed;
+		plaquey = 240;
+		// no break or return here!
+	case 0:
+		//
+		// pic is moving from the bottom to the center of the screen
+		//
+		plaquey -= (elapsed - lastframe) << 1;
+		if (plaquey < 100)
+		{
+			plaquey = 100;
+			plaquephase++;
+		}
+		lastframe = elapsed;
+		return plaquey - (plaqueheight >> 1);
+
+	case 1:
+		//
+		// pic is staying at the center position
+		//
+		if (elapsed - lastframe > 200)
+		{
+			plaquephase++;
+			lastframe = elapsed;
+		}
+		return 100 - (plaqueheight >> 1);
+
+	case 2:
+		//
+		// pic is moving up from the center to the top of the screen
+		//
+		plaquey -= (elapsed - lastframe) << 1;
+		if (plaquey < -40)
+		{
+			plaquey = -40;
+			if (++plaque < 4)
+			{
+				plaquephase = -1;
+			}
+			else
+			{
+				plaquephase = 3;
+			}
+		}
+		lastframe = elapsed;
+		return plaquey - (plaqueheight >> 1);
+	}
+
+	return -40;
+}
+
+/*
+============================
+=
+= SlideLetters
+=
+============================
+*/
+
+void SlideLetters(void)
+{
+	Sint16 x, cPosX, screenxb;
+	Uint16 elapsed, totaltics, dstofs;
+	Sint16 cStart, cEnd, cTotalMove;
+	Uint16 shift, srcseg, srcofs;
+	Sint16 clearleft, copywidth, clearright;
+	Uint16 srcdif, dstdif;
+	Sint32 now;
+
+	//
+	// set up characteristics of the animation
+	//
+	EGAWRITEMODE(0);
+	EGAREADMAP(0);	// useless...
+
+	keenstart = keen->width + 200;
+	EGAREADMAP(1);	// also useless ... I think...
+
+	cEnd = 120 - commander->width;
+	cStart = 320;
+	cTotalMove = cEnd - cStart;
+	totaltics = abs(cTotalMove);
+
+	pageofs = pageon = 0;
+	lasttimecount = TimeCount;
+	while (TimeCount == lasttimecount);
+	lasttimecount = TimeCount;
+
+	for (elapsed=0; elapsed <= totaltics; elapsed += tics)
+	{
+		//
+		// draw the credits pic
+		//
+		x = ((Sint32)keenstart * (Sint32)(totaltics-elapsed)) / (Sint32)totaltics;
+		DrawPlaque(elapsed, x);
+
+		//
+		// get ready to draw draw the "COMMANDER" pic
+		//
+		cPosX = cStart + ((Sint32)cTotalMove * (Sint32)elapsed) / (Sint32)totaltics;
+		cPosX += x & 7;
+		screenxb = (cPosX + 0x800) / 8 + -0x100;
+		shift = (cPosX + 0x800) & 7;
+		srcseg = FP_SEG(cmdrshifts[shift]);
+		srcofs = 0;
+		dstofs = pageofs + x / 8;
+		if (screenxb > 0)
+		{
+			clearleft = (screenxb + 1) / 2;
+			if (screenxb & 1)
+				dstofs--;
+			copywidth = 21 - clearleft;
+			clearright = 0;
+		}
+		else if (-commanderbwide + 40 < screenxb)
+		{
+			clearleft = 0;
+			copywidth = 21;
+			clearright = 0;
+			srcofs -= screenxb;
+		}
+		else
+		{
+			clearleft = 0;
+			copywidth = (commanderbwide + screenxb) / 2;
+			clearright = 21 - copywidth;
+			srcofs -= screenxb;
+		}
+		srcdif = commanderbwide - copywidth*2;
+		dstdif = 248 - (clearleft + copywidth + clearright)*2;
+
+		//
+		// draw "COMMANDER" pic
+		//
+		EGAMAPMASK(2);
+
+		asm {
+			mov	di, dstofs;
+			mov	es, screenseg;
+			mov	si, srcofs;
+			mov	lastsource, si;
+			mov	ds, srcseg;
+			mov	dx, 200;
+		}
+yloop:
+		asm {
+			xor	ax, ax;
+			mov	cx, clearleft;
+			rep stosw;
+			mov	cx, copywidth;
+			rep movsw;
+			xor	ax, ax;
+			mov	cx, clearright;
+			rep stosw;
+			test	dx, 1;
+			jnz	oddline;
+			mov	si, ss:lastsource;
+			jmp	nextline;
+		}
+oddline:
+		asm {
+			add	si, srcdif;
+			mov	ss:lastsource, si;
+		}
+nextline:
+		asm {
+			add	di, dstdif;
+			dec	dx;
+			jnz	yloop;
+			mov	ax, ss;
+			mov	ds, ax;
+		}
+
+		//
+		// page flip
+		//
+		VW_SetScreen(pageofs + x / 8, x & 7);
+		pageon ^= 1;
+		if (pageon)
+		{
+			pageofs = 124;
+		}
+		else
+		{
+			pageofs = 0;
+		}
+
+		//
+		// handle timing
+		//
+		do
+		{
+			now = TimeCount;
+			tics = now - lasttimecount;
+		} while (tics < 2);
+		lasttimecount = now;
+
+		//
+		// handle input
+		//
+		if (IN_IsUserInput() && LastScan != sc_F1)
+		{
+			LastScan = sc_Space;
+		}
+		if (LastScan)
+			return;
+	}
+
+	byteadjust = x / 8;
+}
+
+/*
+============================
+=
+= DrawScan
+=
+============================
+*/
+
+void DrawScan(Sint16 far *source, Uint8 far *dest)
+{
+	register Uint16 x;
+	register Sint16 w;
+	register Uint16 val;
+	register Uint16 i;
+
+	val = x = 0;
+	for (;;)
+	{
+		//
+		// first part: puts black pixels (<width> pixels wide)
+		//
+		w = *source++;
+		if (w == -1)
+		{
+			*dest++ = val;
+			*dest = 0;
+			return;
+		}
+
+		x += w;
+		if (x > 7)
+		{
+			*dest++ = val;
+			val = 0;
+			i = (x / 8) - 1;
+			while (i--)
+			{
+				*dest++ = 0;
+			}
+			x &= 7;
+		}
+
+		//
+		// second part: puts white pixels (<width> pixels wide)
+		//
+		w = *source++;
+		if (w == -1)
+		{
+			*dest++ = val;
+			*dest = 0;
+			return;
+		}
+
+		val |= ortoend[x];
+		x += w;
+		if (x > 7)
+		{
+			*dest++ = val;
+			val = 0xFF;
+			i = (x / 8) - 1;
+			while (i--)
+			{
+				*dest++ = 0xFF;
+			}
+			x &= 7;
+		}
+		val &= andtoend[x];
+	}
+}
+
+/*
+============================
+=
+= BuildScaleShape
+=
+============================
+*/
+
+void BuildScaleShape(void)
+{
+	Sint16 px, w;
+	Sint16 far *source;
+	Sint16 far *dest;
+	Sint16 y;
+
+	MM_GetPtr((memptr*)&both, 30000);
+	dest = MK_FP(FP_SEG(both), sizeof(shapehead));
+
+	for (y=0; y<200; y++)
+	{
+		both->rowofs[y] = FP_OFF(dest);
+		px = 0;
+
+		EGAREADMAP(1);	// this is pretty useless, we're not reading from EGA memory here
+
+		source = (Sint16 far *)((byte _seg *)commander + commander->rowofs[y]);
+		w = *source++;
+		do
+		{
+			*dest++ = px;
+			px = px + w;
+			w = *source++;
+		} while (w != -1);
+
+		//
+		// insert an 80 pixel gap between "COMMANDER" and "KEEN"
+		//
+		// This assumes that the rightmost column(s) of the "COMMANDER"
+		// shape are black. Otherwise the gap would be filled with
+		// white pixels and the "KEEN" image would use inverted colors
+		// as a result.
+		//
+		px += 80;
+
+		EGAREADMAP(0);	// this is pretty useless, we're not reading from EGA memory here
+
+		source = (Sint16 far *)((byte _seg *)keen + keen->rowofs[y]);
+		source++;	// kludgy bit, causes errors when left egde of "KEEN" is no rectangle
+		w = *source++;
+		do
+		{
+			*dest++ = px;
+			px = px + w;
+			w = *source++;
+		} while (w != -1);
+
+		*dest++ = px;	// put last value
+		*dest++ = -1;	// put end-of-line
+	}
+}
+
+/*
+============================
+=
+= ScalePointScan
+=
+============================
+*/
+
+void ScalePointScan(Sint16 far *rowptr, Sint16 y, Sint16 toleft, Sint16 far *scaletable)
+{
+	Uint8 far *dest;
+	Sint16 left, endx;
+	Uint16 w, val, x, right;
+	register Sint16 px, sx;
+
+	val = x = 0;
+	endx = 320 - toleft;
+	dest = MK_FP(0xA000, pageofs + byteadjust + ylookup[y]);
+
+	if (toleft < 0)
+	{
+		left = -toleft;
+		val = 0;
+		x = 0;
+
+		for (;;)
+		{
+			px = *rowptr++;
+			sx = scaletable[px];
+			if (sx > left)
+				goto drawwhite;
+
+			px = *rowptr++;
+			sx = scaletable[px];
+			if (sx > left)
+				goto drawblack;
+		}
+	}
+
+	//
+	// regular
+	//
+	val = 0;
+	x = toleft & 7;
+	dest += (toleft >> 3);
+	left = 0;
+	rowptr++;	// the first value is always 0, we need the next value
+drawloop:
+	px = *rowptr++;
+	sx = scaletable[px];
+
+	//
+	// draw/add black pixels
+	//
+drawblack:
+	w = sx - left;
+	left = sx;
+	x += w;
+	if (x > 7)
+	{
+		asm {
+			les	di, dest;
+			mov	al, BYTE PTR val;
+			stosb;
+			mov	cx, x;
+			shr	cx, 1;
+			shr	cx, 1;
+			shr	cx, 1;
+			dec	cx;
+			xor	al, al;
+			mov	BYTE PTR val, al;
+			rep stosb;
+			and	x, 7;
+			mov	WORD PTR dest, di;
+		}
+	}
+
+	//
+	// stop if the right side of the screen is reached
+	//
+	if (sx > endx)
+		return;
+
+	//
+	// stop if the end of the image row is reached
+	// 
+	// This is only checked after drawing the black part, so the
+	// combined shape must not end with white pixels on the right.
+	// That means the rightmost column(s) of the "KEEN" shape must
+	// always be black.
+	//
+	px = *rowptr++;
+	if (px == -1)
+		goto clearright;
+
+	sx = scaletable[px];
+
+	//
+	// draw/add white pixels
+	//
+drawwhite:
+	w = sx - left;
+	left = sx;
+	val |= ortoend[x];
+	x += w;
+	if (x > 7)
+	{
+		asm {
+			les	di, dest;
+			mov	al, BYTE PTR val;
+			stosb;
+			mov	cx, x;
+			shr	cx, 1;
+			shr	cx, 1;
+			shr	cx, 1;
+			dec	cx;
+			mov	al, 255;
+			mov	BYTE PTR val, al;
+			rep stosb;
+			and	x, 7;
+			mov	WORD PTR dest, di;
+		}
+	}
+
+	//
+	// stop if the right side of the screen is reached
+	//
+	if (sx > endx)
+		return;
+
+	val &= andtoend[x];
+	goto drawloop;
+
+	//
+	// clear the right side of the screen
+	//
+clearright:
+	w = 320 - left;
+	x += w;
+	if (x > 7)
+	{
+		*dest++ = val;
+		val = 0;
+		right = x / 8 - 1;
+		while (right--)
+		{
+			*dest++ = 0;
+		}
+		x &= 7;
+		return;
+	}
+	return;
+}
+
+/*
+============================
+=
+= ScaleDown
+=
+============================
+*/
+
+void ScaleDown(void)
+{
+	Uint16 i;
+	Uint16 toleft, ticselapsed, ticstotal, scale, endscale, rownum, rowinc;
+	Sint32 now;
+	Sint16 far *rowptr;
+	Uint16 scaleheight, top, bottom, lastbottom[2];
+	Sint32 leftorigin;
+
+	//
+	// set our new palette
+	//
+	SetPalette(termcolors2);
+
+	EGAREADMAP(1);	// this is pretty useless, we're not reading from EGA memory here
+
+	leftorigin = 120l - commander->width;
+	BuildScaleShape();
+	MM_GetPtr(&scaletable, 2500*sizeof(Uint16));
+
+	scale = 0x100;		// 100%
+	endscale = 0x21;	// 13% (scale from 200px to 26px)
+	endscale = 0x21;	// redundant
+	lastbottom[0] = lastbottom[1] = 200;
+	ticselapsed = 1;
+	ticstotal = 30;	// time for the whole shrinking animation
+
+	while (ticselapsed <= ticstotal)
+	{
+		//
+		// get current scaling
+		//
+		if (ticselapsed == ticstotal)
+		{
+			scale = endscale;
+			toleft = 0;
+			top = 4;
+		}
+		else
+		{
+			scale = 0x100 - ((0x100-endscale) * ticselapsed) / ticstotal;
+			toleft = (leftorigin * (ticstotal - ticselapsed)) / ticstotal;
+			top = (ticselapsed * 4) / ticstotal;
+		}
+
+		//
+		// build scale table:		scaletable[i] = (i*scale) / 0x100;
+		//
+		asm {
+			xor	ax, ax;
+			xor	dx, dx;
+			mov	cx, 2500;
+			mov	bx, scale;
+			mov	es, scaletable;
+			xor	di, di;
+		}
+l1:
+		asm {
+			mov	es:[di], ah;
+			inc	di;
+			mov	es:[di], dl;
+			inc	di;
+			add	ax, bx;
+			adc	dx, 0;
+			loop	l1;
+		}
+
+		//
+		// wait... didn't we already do this?
+		//
+		if (ticselapsed == ticstotal)
+		{
+			toleft = 0;
+		}
+		else
+		{
+			toleft = (leftorigin * (ticstotal - ticselapsed)) / ticstotal;
+		}
+
+		//
+		// prepare scaled drawing process
+		//
+		scaleheight = ((Sint16 _seg *)scaletable)[200];
+		rownum = 0;
+		rowinc = 0x10000l / scale;
+		bufferofs = pageofs + byteadjust;
+
+		//
+		// erase stuff at the top
+		//
+		if (top > 0)
+		{
+			VW_Bar(0, 0, 320, top, BLACK);
+		}
+
+		//
+		// draw the scaled shape
+		//
+		EGAWRITEMODE(0);
+		EGAMAPMASK(15);
+
+		for (i=0; i<scaleheight; i++)
+		{
+			rowptr = (Sint16 far *)((byte _seg *)both + both->rowofs[rownum >> 8]);
+			ScalePointScan(rowptr, i+top, toleft, scaletable);
+
+			rownum += rowinc;
+		}
+
+		//
+		// erase leftovers at the bottom of the screen
+		//
+		bufferofs = pageofs + byteadjust;
+		bottom = scaleheight + top;
+		if (lastbottom[pageon] > bottom)
+		{
+			VW_Bar(0, bottom, 320, lastbottom[pageon] - bottom, BLACK);
+			lastbottom[pageon] = bottom;
+		}
+
+		//
+		// page flip
+		//
+		VW_SetScreen(pageofs+byteadjust, 0);
+		pageon ^= 1;
+		if (pageon)
+		{
+			pageofs = 124;
+		}
+		else
+		{
+			pageofs = 0;
+		}
+
+		//
+		// handle timing
+		//
+		now = TimeCount;
+		tics = now - lasttimecount;
+		lasttimecount = now;
+		if (tics > 8)
+			tics = 8;	// don't skip too many frames on slow systems
+
+		if (ticselapsed == ticstotal)
+			break;
+
+		ticselapsed += tics;
+		if (ticselapsed > ticstotal)
+			ticselapsed = ticstotal;
+
+		//
+		// handle input
+		//
+		if (IN_IsUserInput() && LastScan != sc_F1)
+		{
+			LastScan = sc_Space;
+		}
+		if (LastScan)
+			return;	// BUG: buffers aren't freed!
+	}
+
+	//
+	// free the buffers
+	//
+	MM_FreePtr(&scaletable);
+	MM_FreePtr((memptr*)&both);
+}
+
+/*
+============================
+=
+= FinishPage
+=
+============================
+*/
+
+void FinishPage(void)
+{
+	Sint16 swap, temp, i, n, x, y;
+	Uint16 ofs;
+	Sint16 top, bottom, delta;
+	Uint8 bitmask[] = {0x01, 0x02, 0x04, 0x08, 0x10, 0x20, 0x40, 0x80};
+	Sint16 xtable[320], ytable[200];
+
+	//
+	// build lookup tables
+	//
+	for (i=0; i<320; i++)
+	{
+		xtable[i] = i;
+	}
+	for (i=0; i<320; i++)
+	{
+		swap = random(320);
+		temp = xtable[swap];
+		xtable[swap] = xtable[i];
+		xtable[i] = temp;
+	}
+	for (i=0; i<200; i++)
+	{
+		ytable[i] = xtable[i];
+	}
+
+	//
+	// set up display
+	//
+	VW_SetDefaultColors();
+	if (pageon)
+	{
+		bufferofs = byteadjust + 124;
+		displayofs = byteadjust;
+	}
+	else
+	{
+		bufferofs = byteadjust;
+		displayofs = byteadjust + 124;
+	}
+	VW_SetScreen(displayofs, 0);
+
+	//
+	// draw title pic to the non-displayed buffer
+	//
+	VW_DrawPic(0, 0, TITLEPICPIC);
+
+	//
+	// copy "random" pixels from the non-displayed area
+	// into the displayed area to create the "fizzle" effect
+	//
+	delta = displayofs - bufferofs;
+
+	//
+	// set ES register for the pixel copying code in the loops
+	//
+	// This is faster than setting the ES register in the loops,
+	// but you need to make sure nothing in the loops overwrites
+	// the ES register, otherwise the code won't work correctly.
+	//
+	asm	mov	es, screenseg;
+
+	for (i = 0; i< 360; i++)
+	{
+		top = i - 160;
+		if (top < 0)
+			top = 0;
+
+		bottom = i;
+		if (bottom >= 200)
+			bottom = 199;
+
+		for (y = top; y <= bottom; y++)
+		{
+			ofs = bufferofs + ylookup[y];
+			for (n=0; n<2; n++)
+			{
+				x = xtable[ytable[y]];
+				if (++ytable[y] == 320)
+				{
+					ytable[y] = 0;
+				}
+
+				//
+				// set bitmask for our x value
+				//
+				asm	mov	cx, x;
+				asm	mov	si, cx;
+				asm	and	si, 7;
+				asm	cli;
+				asm	mov	dx, GC_INDEX;
+				asm	mov	al, GC_BITMASK;
+				asm	mov	ah, BYTE PTR bitmask[si];
+				asm	out	dx, ax;
+				asm	sti;
+
+				//
+				// set up source and dest index registers
+				//
+				asm	mov	si, ofs;
+				asm	shr	cx, 1;
+				asm	shr	cx, 1;
+				asm	shr	cx, 1;
+				asm	add	si, cx;
+				asm	mov	di, si;
+				asm	add	di, delta;
+
+				//
+				// copy the pixel data (all 4 planes)
+				//
+				// "blue" plane:
+				asm	mov	dx, SC_INDEX;
+				asm	mov	ax, SC_MAPMASK + 1*256;
+				asm	out	dx, ax;
+				asm	mov	dx, GC_INDEX;
+				asm	mov	ax, GC_READMAP + 0*256;
+				asm	out	dx, ax;
+				asm	mov	bl, es:[si];
+				asm	xchg	bl, es:[di];
+				// "green" plane:
+				asm	mov	dx, SC_INDEX;
+				asm	mov	ax, SC_MAPMASK + 2*256;
+				asm	out	dx, ax;
+				asm	mov	dx, GC_INDEX;
+				asm	mov	ax, GC_READMAP + 1*256;
+				asm	out	dx, ax;
+				asm	mov	bl, es:[si];
+				asm	xchg	bl, es:[di];
+				// "red" plane:
+				asm	mov	dx, SC_INDEX;
+				asm	mov	ax, SC_MAPMASK + 4*256;
+				asm	out	dx, ax;
+				asm	mov	dx, GC_INDEX;
+				asm	mov	ax, GC_READMAP + 2*256;
+				asm	out	dx, ax;
+				asm	mov	bl, es:[si];
+				asm	xchg	bl, es:[di];
+				// "intensity" plane:
+				asm	mov	dx, SC_INDEX;
+				asm	mov	ax, SC_MAPMASK + 8*256;
+				asm	out	dx, ax;
+				asm	mov	dx, GC_INDEX;
+				asm	mov	ax, GC_READMAP + 3*256;
+				asm	out	dx, ax;
+				asm	mov	bl, es:[si];
+				asm	xchg	bl, es:[di];
+			}
+		}
+
+		VW_WaitVBL(1);	// so the fizzle animation won't go super fast
+
+		if (IN_IsUserInput() && LastScan != sc_F1)
+		{
+			LastScan = sc_Space;
+		}
+		if (LastScan)
+		{
+			EGABITMASK(0xFF);
+			EGAMAPMASK(15);
+			return;
+		}
+	}
+
+	//
+	// clean up EGA registers
+	//
+	EGABITMASK(0xFF);
+	EGAMAPMASK(15);
+
+	//
+	// pause for 6 seconds
+	//
+	IN_UserInput(6 * TickBase, false);
+}
+
+/*
+============================
+=
+= Terminator
+=
+============================
+*/
+
+void Terminator(void)
+{
+	Uint16 i, shift, bufsize;
+	Sint16 far *source;
+	Uint8 far *dest;
+	Uint16 srcseg, destseg;
+	boolean pagefinished;
+	Uint16 rowofs[200];
+
+	pagefinished = false;
+	CA_SetAllPurge();
+	SetPaletteEx(colors[0]);	// all black
+	VW_ClearVideo(BLACK);
+	VW_SetLineWidth(248);	// 1984 pixels total, we're using 992 per "page"
+
+	CA_CacheGrChunk(TITLEPICPIC);
+	CA_CacheGrChunk(BIGCOMMANDER);
+	CA_CacheGrChunk(BIGKEEN);
+	keen = grsegs[BIGKEEN];
+	commander = grsegs[BIGCOMMANDER];
+
+	EGAMAPMASK(1);
+
+	keenstart = keen->width + 200;
+	VW_SetScreen((keenstart/8)+1, 0);
+
+	//
+	// draw the "KEEN" pic (to first "page")
+	//
+	for (i=0; i<200; i++)
+	{
+		source = (Sint16 far *)((byte _seg *)keen + keen->rowofs[i]);
+		dest = MK_FP(0xA000, ylookup[i]);
+		dest += 25;	// 25 bytes -> 200 pixels
+		DrawScan(source, dest);
+	}
+	//
+	// copy pic from first "page" to second "page"
+	//
+	VW_ScreenToScreen(0, 124, 109, 200);
+
+	//
+	// create pre-shifted image buffers for the "COMMANDER" pic
+	// (only 100 pixels high instead of 200 pixels to save memory)
+	//
+	commanderbwide = (commander->width + 7) / 8;
+	commanderbwide = (commanderbwide + 3) & ~1;
+	bufsize = commanderbwide * 100;	// half height
+	for (shift = 0; shift < 8; shift++)
+	{
+		MM_GetPtr(&cmdrshifts[shift], bufsize);
+	}
+
+	//
+	// re-assign shape pointers (memory manager might have moved the buffers)
+	//
+	keen = grsegs[BIGKEEN];
+	commander = grsegs[BIGCOMMANDER];
+
+	//
+	// draw the first (unshifted) version of the "COMMANDER" pic to the buffer
+	//
+	for (i=0; i<100; i++)
+	{
+		rowofs[i*2] = rowofs[i*2+1] = i * commanderbwide;
+		source = (Sint16 far *)((byte _seg *)commander + commander->rowofs[i*2]);
+		dest = (Uint8 _seg *)cmdrshifts[0] + rowofs[i*2];
+		DrawScan(source, dest);
+	}
+
+	//
+	// create the shifted versions of the "COMMANDER" pic
+	//
+	for (shift = 1; shift < 8; shift++)
+	{
+		srcseg = FP_SEG(cmdrshifts[shift-1]);
+		destseg = FP_SEG(cmdrshifts[shift]);
+		asm {
+			mov	ds, srcseg;
+			mov	es, destseg;
+			mov	cx, bufsize;
+			clc;
+			xor	si, si;
+			xor	di, di;
+		}
+l1:
+		asm {
+			lodsb;
+			rcr	al, 1;
+			stosb;
+			loop	l1;
+			mov	ax, ss;
+			mov	ds, ax;
+		}
+	}
+
+	//
+	// prepare (and set) the palettes
+	//
+	termcolors[16] = termcolors2[16] = termcolors[16] = bordercolor;
+	SetPalette(termcolors);
+
+	//
+	// cache the credits pics (they are converted into a special
+	// format to make shifted drawing easier during the animation)
+	//
+	for (i=0; i<4; i++)
+	{
+		LoadPlaque(i);
+	}
+
+	//
+	// play the animation
+	//
+	plaque = lastframe = 0;
+	plaquephase = -1;
+	SlideLetters();
+
+	//
+	// free some of the buffers
+	// (shrink animation needs additional memory)
+	//
+	for (i=0; i<4; i++)
+	{
+		MM_FreePtr(&basepl[i]);
+	}
+	for (shift=0; shift<8; shift++)
+	{
+		MM_FreePtr(&cmdrshifts[shift]);
+	}
+
+	//
+	// do the shrinking and fizzle fade animations
+	// (if intro wasn't aborted)
+	//
+	if (!LastScan)
+	{
+		ScaleDown();
+	}
+
+	if (!LastScan)
+	{
+		FinishPage();
+		pagefinished = true;
+	}
+
+	//
+	// free the remaining buffers
+	//
+	MM_SetPurge(&grsegs[BIGCOMMANDER], 3);
+	MM_SetPurge(&grsegs[BIGKEEN], 3);
+
+	//
+	// switch back to default graphics settings
+	//
+	VW_ClearVideo(BLACK);
+	VW_SetLineWidth(SCREENWIDTH);
+	VW_SetDefaultColors();
+	RF_FixOfs();
+	CA_ClearMarks();
+
+	//
+	// handle input and main menu stuff
+	//
+	if (LastScan == sc_None)
+	{
+		return;
+	}
+#ifndef KEEN6
+	if (LastScan == sc_F1)
+	{
+		HelpScreens();
+		return;
+	}
+#endif
+	if (!pagefinished)
+	{
+		RF_FixOfs();	//redundant
+		CA_CacheGrChunk(TITLEPICPIC);
+		VW_DrawPic(0, 0, TITLEPICPIC);
+		VW_SetScreen(bufferofs, 0);
+		IN_Ack();
+		CA_ClearMarks();
+		if (storedemo)
+		{
+			playstate = ex_resetgame;
+			restartgame = gd_Normal;
+			IN_ClearKeysDown();
+			NewGame();
+			return;
+		}
+	}
+
+	US_ControlPanel();
+	if (restartgame)
+	{
+		playstate = ex_resetgame;
+	}
+	else if (loadedgame)
+	{
+		playstate = ex_loadedgame;
+	}
+}
+
+/*
+=============================================================================
+
+							STAR WARS TEXT CRAWL
+
+=============================================================================
+*/
+
+/*
+============================
+=
+= BuildBitTables
+=
+============================
+*/
+
+void BuildBitTables(void)
+{
+	Uint16 bit1, bit2, i;
+	Uint8 far *buffer;
+
+	MM_GetPtr(&bittables, 0x4000);
+	buffer = bittables;
+
+	//
+	// generate a lookup table that maps the bits of the "texture" (bit1)
+	// to the appropriate bit for the screen position (bit2) to make the
+	// scaler code faster and smaller
+	//
+	// table[((7-b1)*8+(7-b2))*256+i] = (i & (1 << (7-b1))) ? (1 << (7-b2)) : 0;
+	//
+	for (bit1 = 1; bit1 < 0x100; bit1 <<= 1)
+	{
+		for (bit2 = 1; bit2 < 0x100; bit2 <<= 1)
+		{
+			for (i = 0; i < 0x100; i++, buffer++)
+			{
+				if (i & bit1)
+				{
+					*buffer = bit2;
+				}
+				else
+				{
+					*buffer = 0;
+				}
+			}
+		}
+	}
+}
+
+/*
+============================
+=
+= CompileSWUpdate
+=
+============================
+*/
+
+void CompileSWUpdate(void)
+{
+	Sint16 y;
+	Uint16 i, width, scalestep, step;
+	Sint32 scale, rowof, xpos, size;
+	void far *buffer;
+	Uint8 srcoff, srcbit, bitpos;
+	Uint16 destoff, srcx, left, orindex, lastoff;
+
+	BuildBitTables();
+	size = 190000;
+	MM_GetPtr(&linecode, size);
+	buffer = linecode;
+	//
+	// Note: You should really lock the pointer to prevent the memmory manager
+	// from moving the buffer around. This code stores a bunch of pointers to
+	// this memory block in the linestarts array. Those pointers will not be
+	// updated when the memory manager moves the buffer around and the game
+	// might end up crashing (or worse) when trying to run the "code" at the
+	// memory location after the data was moved. The game starts playing music
+	// after this function is done, which may or may not cause the memory
+	// manager to move memory blocks around.
+	//
+
+	//
+	// move the buffer address into ES:DI (and keep it there)
+	//
+	asm	mov	es, WORD PTR buffer+2;
+	asm	mov	di, WORD PTR buffer;
+	//
+	// Since the address is kept in ES:DI, we must save and restore
+	// the ES register when calling other functions (push es / pop es).
+	// The Borland C compiler always saves and restores the DI register
+	// when a function modifies it, so we don't need to worry about
+	// that register. This is a bit of an ugly hack, but it makes this
+	// code a little faster and smaller.
+	//
+
+	scale = 320l << 11;
+	scalestep = (((Uint32)(320-40) << 11) / 200);	// roughly 1.4 pixels per step, going from 320 pixels to 40 pixels in 200 steps
+	rowof = 0;
+
+	for (y=199; y >= 0; y--)
+	{
+		//
+		// draw a blue line for the current row
+		//
+		asm	push	es;
+		VW_Hlin(0, 320, y, BLUE);
+		asm	pop	es;
+
+		//
+		// update the buffer variable with the current (normalized) ES:DI address
+		//
+		asm	mov	WORD PTR buffer, di;
+		asm	mov	WORD PTR buffer+2, es;
+
+		//
+		// store the address in the scaler lookup table
+		//
+		linestarts[y] = buffer;
+
+		//
+		// get current scaling factors
+		//
+		width = ((Uint16)((scale/2) >> 11)) << 1;	// some trickery to make sure width is even
+		sourceline[y] = (rowof >> 11);
+		step = (336l << 11) / width;
+		xpos = 0;
+		rowof += step;
+		left = 160 - (width >> 1);
+		destoff = ylookup[y] + left / 8;
+		bitpos = left & 7;
+
+		//
+		// generate the machine code
+		//
+		//		MOV	CX, SS
+		//		MOV	SS, AX
+		//		ADD	DI, <destoff>
+		//		XOR	AL, AL
+		//
+		asm	mov	ax, 0D18Ch;
+		asm	stosw;
+		asm	mov	ax, 0D08Eh;
+		asm	stosw;
+		asm	mov	ax, 0C781h;
+		asm	stosw;
+		asm	mov	ax, destoff;
+		asm	stosw;
+		asm	mov	ax, 0C030h;
+		asm	stosw;
+
+		lastoff = -1;
+		for (i=0; i<width; i++)
+		{
+			srcx = (xpos >> 11);
+			srcoff = (srcx / 8);
+			srcbit = srcx & 7;
+
+			orindex = ((7-srcbit)*8 + 7-bitpos) << 8;
+			if (srcoff != lastoff)
+			{
+				//
+				//		MOV	BL, [BP + <srcoff>]
+				//
+				asm	mov	ax, 5E8Ah;
+				asm	stosw;
+				asm	mov	al, srcoff;
+				asm	stosb;
+
+				lastoff = srcoff;
+			}
+
+			//
+			//		OR		AL, [BX + <orindex>]
+			//
+			asm	mov	ax, 870Ah;
+			asm	stosw;
+			asm	mov	ax, orindex;
+			asm	stosw;
+
+			bitpos++;
+			if (bitpos == 8)
+			{
+				bitpos = 0;
+
+				//
+				//		STOSB
+				//		XOR	AL, AL
+				//
+				asm	mov	ax, 30AAh;
+				asm	stosw;
+				asm	mov	al, 0C0h;
+				asm	stosb;
+			}
+
+			xpos += step;
+		}
+
+		if (bitpos)
+		{
+			//
+			//		STOSB
+			//
+			asm	mov	al, 0AAh;
+			asm	stosb;
+		}
+		//
+		// generate end of subroutine
+		//
+		//		MOV	SS, CX
+		//		RETF
+		//
+		asm	mov	ax, 0D18Eh;
+		asm	stosw;
+		asm	mov	al, 0CBh;
+		asm	stosb;
+
+		//
+		// normalize ES:DI
+		//
+		asm	mov	ax, di;
+		asm	shr	ax, 1;
+		asm	shr	ax, 1;
+		asm	shr	ax, 1;
+		asm	shr	ax, 1;
+		asm	mov	bx, es;
+		asm	add	ax, bx;
+		asm	mov	es, ax;
+		asm	and	di, 0Fh;
+
+		//
+		// update scale value for next row
+		//
+		scale -= scalestep;
+
+		//
+		// replace the blue line with the row from the background image
+		//
+		asm	push	es;
+		VW_ScreenToScreen(ylookup[y] + 0x8000, ylookup[y], 40, 1);
+		asm	pop	es;
+
+		if (LastScan)
+			return;
+	}
+}
+
+/*
+============================
+=
+= TranslateString
+=
+============================
+*/
+
+void TranslateString(char *text)
+{
+	char c;
+
+	while (*text)
+	{
+		c = *text;
+
+		if (c >= 'A' && c <= 'Z')
+		{
+			c = c + -33;
+		}
+		else if (c >= 'a' && c <= 'z')
+		{
+			c = c + -39;
+		}
+		else if (c == '.')
+		{
+			c = 84;
+		}
+		else if (c == ',')
+		{
+			c = 85;
+		}
+		else if (c == '-')
+		{
+			c = 86;
+		}
+		else if (c == '"')
+		{
+			c = 87;
+		}
+		else if (c == ' ')
+		{
+			c = 88;
+		}
+		else if (c == '!')
+		{
+			c = 89;
+		}
+		else if (c == '\'')
+		{
+			c = 90;
+		}
+		else if (c != '\n')
+		{
+			c = 84;	// any unhandled character is drawn as '.'
+		}
+
+		*text++ = c;
+	}
+}
+
+/*
+============================
+=
+= DrawSWText
+=
+============================
+*/
+
+void DrawSWText(void)
+{
+	char far *text;
+	char *ptr;
+	char c;
+	char strbuf[80];
+
+	WindowX = 0;
+	WindowW = 336;
+	PrintY = 1;		// always leave the first line blank
+	bufferofs = 0;
+	panadjust = 0;
+	text = swtext;
+	masterlines = 0;
+
+	//
+	// draw the entire text to video memory
+	//
+	while (*text)
+	{
+		ptr = strbuf;
+		do
+		{
+			c = *text++;
+			*ptr++ = c;
+		} while (c != '\n' && c != '\0');
+		*ptr = '\0';
+
+		TranslateString(strbuf);
+
+		US_CPrint(strbuf);
+
+		bufferofs += ylookup[PrintY];
+		masterlines += PrintY;
+		PrintY = 0;
+	}
+
+	//
+	// allocate a buffer large enough to hold the entire text image
+	// and move the image data from video memory into that buffer
+	//
+	MM_GetPtr(&sourcepic, bufferofs);
+	EGAREADMAP(1);	// read from "green" plane (doesn't really matter from which plane we read)
+	movedata(screenseg, 0, FP_SEG(sourcepic), 0, bufferofs);
+
+	//
+	// erase the (first screen of the) text from video memory.
+	// we're going to display this area and copy the backgound pic
+	// here line-by-line as the scalers are generated and we don't
+	// want to have parts of the text still visible at that point.
+	//
+	bufferofs = 0;
+	VW_Bar(0, 0, 320, 200, BLACK);
+}
+
+/*
+============================
+=
+= ScrollSWText
+=
+============================
+*/
+
+void ScrollSWText(void)
+{
+	Sint32 now;
+	Uint16 pos;
+	Sint16 i, rowof;
+
+	tics = TimeCount = lasttimecount = 0;
+
+	EGAWRITEMODE(0);
+	EGAMAPMASK(8);	// only draw to the "intensity" plane (so we don't erase the backgound pic)
+
+	pos = 0;
+	while (masterlines + 400 >= pos)
+	{
+		for (i = 199; i >= 0; i--)
+		{
+			rowof = pos - sourceline[i];
+			if (rowof < 0 || rowof >= masterlines)
+			{
+				masterofs = 0;	// draw the first (blank) line of the buffer
+			}
+			else
+			{
+				masterofs = rowof * 42;
+			}
+			routine = linestarts[i];
+			asm {
+				mov	es, screenseg;
+				mov	di, pageofs;
+				mov	ds, bittables;
+				push	bp;
+				mov	bp, ss:masterofs;
+				mov	ax, ss:sourcepic;
+				xor	bh, bh;
+				cli;	// disable interrupts (scaler changes register SS, so interrupts would be fatal!)
+				call	ss:routine;
+				sti;	// enable interrupts again
+				pop	bp;
+				mov	ax, ss;
+				mov	ds, ax;
+			}
+		}
+
+		VW_SetScreen(pageofs, 0);
+		pageon ^= 1;
+		pageofs = pageon << 15;
+
+		now = TimeCount;
+		tics = tics + (now - lasttimecount);
+		lasttimecount = now;
+		if (tics > 20)
+			tics = 20;
+
+		pos = pos + tics / 4;
+		tics &= 3;
+
+		if (IN_IsUserInput() && LastScan != sc_F1)
+			LastScan = sc_Space;
+
+		if (LastScan)
+			break;
+	}
+}
+
+/*
+============================
+=
+= StarWars
+=
+============================
+*/
+
+void StarWars(void)
+{
+	SetPaletteEx(colors[0]);	// all black
+	VW_ClearVideo(BLACK);
+	VW_SetLineWidth(42);	// 336 pixels
+	VW_SetScreen(0, 0);
+	pageon = pageofs = 0;
+	CA_SetAllPurge();
+	CA_CacheGrChunk(STARTFONT+2);
+	fontnumber = 2;
+	DrawSWText();
+	fontnumber = 0;
+
+	CA_CacheGrChunk(SW_BACKGROUNDPIC);
+	bufferofs = 0x8000;
+	VW_DrawPic(0, 0, SW_BACKGROUNDPIC);
+	CA_SetAllPurge();
+	SetPaletteEx(starcolors);
+	bufferofs = 0;
+	CompileSWUpdate();
+
+	if (!LastScan)
+	{
+		StartMusic(STARWARSMUSIC);
+		ScrollSWText();
+		StopMusic();
+	}
+
+	MM_FreePtr(&linecode);
+	MM_FreePtr(&bittables);
+	MM_FreePtr(&sourcepic);
+
+	VW_ClearVideo(BLACK);
+	VW_SetLineWidth(SCREENWIDTH);
+	VW_SetDefaultColors();
+	RF_FixOfs();
+	CA_ClearMarks();
+
+	CheckLastScan();
+}
+
+#endif	// if GRMODE == EGAGR
+
+//===========================================================================
+
+/*
+============================
+=
+= ShowTitle
+=
+============================
+*/
+
+void ShowTitle(void)
+{
+	panadjust = 0;
+	CA_CacheGrChunk(TITLEPICPIC);
+	VW_DrawPic(0, 0, TITLEPICPIC);
+#if GRMODE == CGAGR
+	VW_UpdateScreen();
+#else
+	VW_SetScreen(displayofs, 0);
+	VW_ScreenToScreen(bufferofs, displayofs, 42, 224);
+#endif
+	IN_UserInput(6*TickBase, false);
+	CA_ClearMarks();
+	CheckLastScan();
+}
+
+//===========================================================================
+
+#if GRMODE == CGAGR
+/*
+============================
+=
+= ShowCredits
+=
+============================
+*/
+
+void ShowCredits(void)
+{
+	panadjust = 0;
+	CA_CacheGrChunk(SW_BACKGROUNDPIC);
+	VW_DrawPic(0, 0, SW_BACKGROUNDPIC);
+	VW_UpdateScreen();
+	IN_UserInput(6*TickBase, false);
+	CA_ClearMarks();
+	CheckLastScan();
+}
+#endif
+
+//===========================================================================
+
+/*
+============================
+=
+= RunDemo
+=
+============================
+*/
+
+void RunDemo(Sint16 num)
+{
+	Uint16 far *demodata;
+	
+	NewGame();
+	num += DEMO0;
+	CA_CacheGrChunk(num);
+	demodata = grsegs[num];
+	gamestate.mapon = demodata[0];
+	DemoSize = demodata[1];
+	MM_GetPtr(&(memptr)DemoBuffer, DemoSize);
+	MM_SetLock(&(memptr)DemoBuffer, true);
+	_fmemcpy(DemoBuffer, ((char _seg *)grsegs[num])+4, DemoSize);
+	MM_FreePtr(&grsegs[num]);
+	IN_StartDemoPlayback(DemoBuffer, DemoSize);
+	SetupGameLevel(true);
+	if (scorescreenkludge)
+	{
+		DrawHighScores();
+	}
+	PlayLoop();
+	IN_StopDemo();
+	MM_FreePtr(&(memptr)DemoBuffer);
+	VW_FixRefreshBuffer();
+	CA_ClearMarks();
+	CheckLastScan();
+}
+
+//===========================================================================
+
+/*
+============================
+=
+= DrawHighScores
+=
+============================
+*/
+
+void DrawHighScores(void)
+{
+	Uint16 i, n;
+	Uint16 width, height;
+	HighScore *entry;
+	Uint16 oldbufferofs;
+	char buf[16], *bufptr;
+	
+	RF_NewPosition(0, 0);
+	oldbufferofs = bufferofs;
+	bufferofs = masterofs;
+#ifdef KEEN5
+#if GRMODE == CGAGR
+	fontcolor = 2;
+#else
+	fontcolor = BLUE ^ LIGHTMAGENTA;	// blue text on light magenta background (XOR draw mode!)
+#endif
+#endif
+	for (i=0, entry=&Scores[0]; i<MaxScores; i++, entry++)
+	{
+		PrintY = i*16 + HIGHSCORE_TOP;
+		PrintX = HIGHSCORE_LEFT;
+		US_Print(entry->name);
+#ifdef KEEN4
+		PrintX = 152;
+		for (n=0; n<entry->completed; n++)
+		{
+			VWB_DrawTile8(PrintX, PrintY+1, 71);
+			PrintX += 8;
+		}
+#endif
+		ultoa(entry->score, buf, 10);
+		for (bufptr=buf; *bufptr; bufptr++)
+		{
+			*bufptr = *bufptr + 81;
+		}
+		USL_MeasureString(buf, &width, &height);
+		PrintX = HIGHSCORE_RIGHT - width;
+		US_Print(buf);
+	}
+	fontcolor = WHITE;	// back to default color
+	bufferofs = oldbufferofs;
+}
+
+//===========================================================================
+
+/*
+============================
+=
+= CheckHighScore
+=
+============================
+*/
+
+void CheckHighScore(Sint32 score, Sint16 completed)
+{
+	Uint16 i, n;
+	Sint16 index;
+	HighScore entry;
+	
+	strcpy(entry.name, "");	//Note: 'entry.name[0] = 0;' would be more efficient
+	entry.score = score;
+	entry.completed = completed;
+	for (i=0, index=-1; i<MaxScores; i++)
+	{
+		if (Scores[i].score < entry.score ||
+			(Scores[i].score == entry.score && Scores[i].completed < entry.completed))
+		{
+			n=MaxScores;
+			while (--n > i)
+			{
+				Scores[n] = Scores[n-1];
+			}
+			Scores[i] = entry;
+			index = i;
+			HighScoresDirty = true;
+			break;
+		}
+	}
+	if (index != -1)
+	{
+		scorescreenkludge = true;
+		gamestate.mapon = HIGHSCORE_MAP;
+		SetupGameLevel(true);
+		DrawHighScores();
+#ifdef KEEN5
+#if GRMODE == CGAGR
+		fontcolor = 2;
+#else
+		fontcolor = BLUE ^ LIGHTMAGENTA;	// blue text on light magenta background (XOR draw mode!)
+#endif
+#endif
+		RF_Refresh();
+		RF_Refresh();
+		PrintY = i*16 + HIGHSCORE_TOP;
+		PrintX = HIGHSCORE_LEFT;
+		US_LineInput(PrintX, PrintY, Scores[index].name, NULL, true, MaxHighName, 112);
+		scorescreenkludge = false;
+	}
+#ifdef KEEN5
+	fontcolor = 15;	// back to default color (white)
+#endif
+}
+
+//===========================================================================
+
+/*
+============================
+=
+= ShowHighScores
+=
+============================
+*/
+
+void ShowHighScores(void)
+{
+	scorescreenkludge = true;
+	IN_ClearKeysDown();
+	RunDemo(4);
+	scorescreenkludge = false;
+}
diff --git a/16/keen456/KEEN4-6/CK_GAME.C b/16/keen456/KEEN4-6/CK_GAME.C
new file mode 100755
index 00000000..157bd3f8
--- /dev/null
+++ b/16/keen456/KEEN4-6/CK_GAME.C
@@ -0,0 +1,1009 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+#include "CK_DEF.H"
+
+/*
+=============================================================================
+
+						 GLOBAL VARIABLES
+
+=============================================================================
+*/
+
+Uint16 fadecount;
+Sint16 levelcompleted;
+Sint32 chunkcount, chunkmax, handpic;
+
+/*
+=============================================================================
+
+						 LOCAL VARIABLES
+
+=============================================================================
+*/
+
+void FadeAndUnhook(void);
+
+//===========================================================================
+
+/*
+============================
+=
+= FreeGraphics
+=
+============================
+*/
+
+void FreeGraphics(void)
+{
+	Sint16 i;
+	for (i=STARTSPRITES; i<STARTSPRITES+NUMSPRITES; i++)
+	{
+		if (grsegs[i])
+		{
+			MM_SetPurge(&grsegs[i], PURGE_LAST);
+		}
+	}
+	for (i=STARTTILE16; i<STARTEXTERNS; i++)
+	{
+		if (grsegs[i])
+		{
+			MM_SetPurge(&grsegs[i], PURGE_LAST);
+		}
+	}
+}
+
+//===========================================================================
+
+/*
+=====================
+=
+= NewGame
+=
+= Set up new game to start from the beginning
+=
+=====================
+*/
+
+void NewGame(void)
+{
+	memset(&gamestate, 0, sizeof(gamestate));
+	gamestate.nextextra = 20000;
+	gamestate.lives = 3;
+	gamestate.ammo = 5;
+}
+
+//===========================================================================
+
+#ifndef KEEN5
+/*
+============================
+=
+= GameOver
+=
+============================
+*/
+
+void GameOver(void)
+{
+	VW_FixRefreshBuffer();
+	US_CenterWindow(16, 3);
+	US_PrintCentered("Game Over!");
+	VW_UpdateScreen();
+	IN_ClearKeysDown();
+	IN_UserInput(4*TickBase, false);
+}
+#endif
+
+//===========================================================================
+
+/*
+============================
+=
+= SaveTheGame
+=
+============================
+*/
+
+#define RLETAG 0xABCD
+
+boolean SaveTheGame(Sint16 handle)
+{
+	Uint16	i,compressed,expanded;
+	objtype	*ob;
+	memptr	bigbuffer;
+
+	gamestate.riding = NULL;
+
+	if (!CA_FarWrite(handle, (byte far *)&gamestate, sizeof(gamestate)))
+		return false;
+
+	expanded = mapwidth * mapheight * 2;
+	MM_GetPtr(&bigbuffer, expanded);
+
+	for (i = 0; i < 3; i++)
+	{
+		compressed = CA_RLEWCompress(mapsegs[i], expanded, (Uint16 huge *)bigbuffer+1, RLETAG);
+		*(Uint16 huge *)bigbuffer = compressed;
+		if (!CA_FarWrite(handle, bigbuffer, compressed+2))
+		{
+			MM_FreePtr(&bigbuffer);
+			return false;
+		}
+	}
+	for (ob = player; ob; ob=ob->next)
+	{
+		if (!CA_FarWrite(handle, (byte far *)ob, sizeof(objtype)))
+		{
+			MM_FreePtr(&bigbuffer);
+			return false;
+		}
+	}
+	MM_FreePtr(&bigbuffer);
+	return true;
+}
+
+//===========================================================================
+
+/*
+============================
+=
+= LoadTheGame
+=
+============================
+*/
+
+boolean LoadTheGame(Sint16 handle)
+{
+	Uint16	i;
+	objtype	*prev,*next,*followed;
+	Uint16	compressed,expanded;
+	memptr	bigbuffer;
+#ifdef KEEN5
+	Sint16	numfuses;
+#endif
+
+	if (!CA_FarRead(handle, (byte far *)&gamestate, sizeof(gamestate)))
+		return false;
+
+#ifdef KEEN5
+	//
+	// remember the fuses value for later - SetupGameLevel calls
+	// ScanInfoPlane, which resets this part of the gamestate
+	//
+	numfuses = gamestate.numfuses;
+#endif
+
+	ca_levelbit >>= 1;
+	ca_levelnum--;
+	SetupGameLevel(false);
+	if (mmerror)
+	{
+		mmerror = false;
+		US_CenterWindow(20, 8);
+		PrintY += 20;
+		US_CPrint("Not enough memory\nto load game!");
+		VW_UpdateScreen();
+		IN_Ack();
+		return false;
+	}
+	ca_levelbit <<= 1;
+	ca_levelnum++;
+
+	expanded = mapwidth * mapheight * 2;
+	MM_BombOnError(true);	//BUG: this should use false to avoid an instant crash
+	MM_GetPtr(&bigbuffer, expanded);
+	MM_BombOnError(false);	//BUG: this should use true to force an instant crash
+	if (mmerror)
+	{
+		mmerror = false;
+		US_CenterWindow(20, 8);
+		PrintY += 20;
+		US_CPrint("Not enough memory\nto load game!");
+		VW_UpdateScreen();
+		IN_Ack();
+		return false;
+	}
+	for (i = 0; i < 3; i++)
+	{
+		if (!CA_FarRead(handle, (byte far *)&compressed, sizeof(compressed)))
+		{
+			MM_FreePtr(&bigbuffer);
+			return false;
+		}
+		if (!CA_FarRead(handle, (byte far *)bigbuffer, compressed))
+		{
+			MM_FreePtr(&bigbuffer);
+			return false;
+		}
+		CA_RLEWexpand(bigbuffer, mapsegs[i], expanded, RLETAG);
+	}
+	MM_FreePtr(&bigbuffer);
+
+	InitObjArray();
+	new = player;
+	prev = new->prev;
+	next = new->next;
+	if (!CA_FarRead(handle, (byte far *)new, sizeof(objtype)))
+	{
+		return false;
+	}
+	new->prev = prev;
+	new->next = next;
+	new->needtoreact = true;
+	new->sprite = NULL;
+	new = scoreobj;
+	while (true)
+	{
+		prev = new->prev;
+		next = new->next;
+		if (!CA_FarRead(handle, (byte far *)new, sizeof(objtype)))
+		{
+			return false;
+		}
+		followed = new->next;
+		new->prev = prev;
+		new->next = next;
+		new->needtoreact = true;
+		new->sprite = NULL;
+		if (new->obclass == stunnedobj)
+		{
+			new->temp3 = 0;	//clear sprite ptr for the stars
+		}
+#if defined KEEN4
+		else if (new->obclass == platformobj)
+		{
+			new->temp2 = new->temp3 = 0;	//clear sprite ptrs
+		}
+#elif defined KEEN5
+		else if (new->obclass == mineobj)
+		{
+			new->temp4 = 0;	//clear sprite ptr
+		}
+		else if (new->obclass == spherefulobj)
+		{
+			new->temp1 = new->temp2 = new->temp3 = new->temp4 = 0;	//clear sprite ptrs
+		}
+#elif defined KEEN6
+		else if (new->obclass == platformobj)
+		{
+			new->temp3 = 0;	//clear sprite ptr
+		}
+#endif
+		if (followed)
+		{
+			GetNewObj(false);
+		}
+		else
+		{
+			break;
+		}
+	}
+	scoreobj->temp2 = -1;
+	scoreobj->temp1 = -1;
+	scoreobj->temp3 = -1;
+	scoreobj->temp4 = -1;
+#ifdef KEEN5
+	gamestate.numfuses = numfuses;	// put value from saved game back in place 
+#endif
+	return true;
+}
+
+//===========================================================================
+
+/*
+============================
+=
+= ResetGame
+=
+============================
+*/
+
+void ResetGame(void)
+{
+	NewGame();
+	ca_levelnum--;
+	ca_levelbit >>= 1;
+	CA_ClearMarks();
+	ca_levelbit <<= 1;
+	ca_levelnum++;
+}
+
+//===========================================================================
+
+
+/*
+==========================
+=
+= PatchWorldMap
+=
+= Takes out blocking squares and spawns flags
+=
+==========================
+*/
+
+void PatchWorldMap(void)
+{
+	Uint16 x, y, planeoff, info, level, tag;
+	Uint16 far *infoptr;
+
+	planeoff = 0;
+	infoptr = mapsegs[2];
+	for (y = 0; y < mapheight; y++)
+	{
+		for (x = 0; x < mapwidth; x++, infoptr++, planeoff++)
+		{
+			info = *infoptr;
+			level = info & 0xFF;
+			if (level >= MINDONELEVEL && level <= MAXDONELEVEL && gamestate.leveldone[level])
+			{
+				tag = info >> 8;
+				*infoptr = 0;	// BUG: infoplane value should only be set to 0 if tag == 0xC0
+				if (tag == 0xD0)
+				{
+					mapsegs[1][planeoff] = 0;
+				}
+				else if (tag == 0xF0)
+				{
+#ifdef KEEN5
+					SpawnFlag(x, y);
+#else
+					if (levelcompleted == level)
+					{
+						SpawnThrowFlag(x, y);
+					}
+					else
+					{
+						SpawnFlag(x, y);
+					}
+#endif
+				}
+			}
+		}
+	}
+}
+
+//===========================================================================
+
+/*
+==========================
+=
+= DelayedFade
+=
+= Fades out and latches FadeAndUnhook onto the refresh
+=
+==========================
+*/
+
+void DelayedFade(void)
+{
+	VW_FadeOut();
+	fadecount = 0;
+	RF_SetRefreshHook(&FadeAndUnhook);
+}
+
+/*
+==========================
+=
+= FadeAndUnhook
+=
+= Latch this onto the refresh so the screen only gets faded in after two
+= refreshes.  This lets all actors draw themselves to both pages before
+= fading the screen in.
+=
+==========================
+*/
+
+void FadeAndUnhook(void)
+{
+	if (++fadecount == 2)
+	{
+		VW_FadeIn();
+		RF_SetRefreshHook(NULL);
+		TimeCount = lasttimecount;	// don't adaptively time the fade
+	}
+}
+
+//===========================================================================
+
+
+/*
+==========================
+=
+= SetupGameLevel
+=
+= Load in map mapon and cache everything needed for it
+=
+==========================
+*/
+
+void SetupGameLevel(boolean loadnow)
+{
+//
+// randomize if not a demo
+//
+	if (DemoMode)
+	{
+		US_InitRndT(false);
+		gamestate.difficulty = gd_Normal;
+	}
+	else
+	{
+		US_InitRndT(true);
+	}
+
+//
+// load the level header and three map planes
+//
+	CA_CacheMap(gamestate.mapon);
+
+//
+// let the refresh manager set up some variables
+//
+	RF_NewMap();
+
+//
+// decide which graphics are needed and spawn actors
+//
+	CA_ClearMarks();
+	ScanInfoPlane();
+	if (mapon == 0)
+	{
+		PatchWorldMap();
+	}
+	RF_MarkTileGraphics();
+
+//
+// have the caching manager load and purge stuff to make sure all marks
+// are in memory
+//
+	MM_BombOnError(false);
+	CA_LoadAllSounds();
+	if (loadnow)
+	{
+		if (scorescreenkludge)
+		{
+			CA_CacheMarks(NULL);
+		}
+		else if (DemoMode)
+		{
+			CA_CacheMarks("DEMO");
+		}
+#ifdef KEEN5
+		else if (mapon == 0 && player->tiletop > 100)
+		{
+			CA_CacheMarks("Keen steps out\nonto Korath III");
+		}
+#endif
+		else
+		{
+			_fstrcpy(str, levelenter[mapon]);
+			CA_CacheMarks(str);
+		}
+	}
+	MM_BombOnError(true);
+
+	if (!mmerror && loadnow)
+	{
+		DelayedFade();
+	}
+}
+
+//===========================================================================
+
+
+/*
+==========================
+=
+= DialogDraw
+=
+==========================
+*/
+
+void DialogDraw(char *title, Uint16 numcache)
+{
+	Sint16 i;
+	Uint16 width, height;
+	Sint32 totalfree;
+
+	totalfree = MM_TotalFree();
+	if (totalfree < 2048)
+	{
+		handpic = 5;
+	}
+	else
+	{
+		handpic = 0;
+		for (i = 0; i < 6; i++)
+		{
+			CA_CacheGrChunk(i+KEENCOUNT1PIC);
+			CA_UnmarkGrChunk(i+KEENCOUNT1PIC);
+			if (grsegs[i+KEENCOUNT1PIC])
+			{
+				MM_SetPurge(&grsegs[i+KEENCOUNT1PIC], PURGE_FIRST);
+			}
+			else
+			{
+				mmerror = false;
+				handpic = 5;
+				break;
+			}
+		}
+	}
+	US_CenterWindow(26, 8);
+	if (grsegs[KEENCOUNT1PIC])
+	{
+		VWB_DrawPic(WindowX, WindowY, KEENCOUNT1PIC);
+	}
+	else
+	{
+		handpic = 5;
+	}
+	CA_UnmarkGrChunk(KEENCOUNT1PIC);	//redundant
+	WindowW -= 48;
+	WindowX += 48;
+	SizeText(title, &width, &height);
+	PrintY += (WindowH-height)/2 - 4;
+	US_CPrint(title);
+	VW_UpdateScreen();
+	chunkmax = chunkcount = numcache / 6;
+	if (!chunkmax && !handpic)
+	{
+		handpic = 5;
+		if (grsegs[KEENCOUNT6PIC])
+			VWB_DrawPic(WindowX-24, WindowY+40, KEENCOUNT6PIC);
+		VW_UpdateScreen();
+	}
+}
+
+/*
+==========================
+=
+= DialogUpdate
+=
+==========================
+*/
+
+void DialogUpdate(void)
+{
+	if (--chunkcount || handpic > 4)
+		return;
+
+	chunkcount = chunkmax;
+	if (grsegs[handpic+KEENCOUNT2PIC])
+	{
+		VWB_DrawPic(WindowX-24, WindowY+40, handpic+KEENCOUNT2PIC);
+	}
+	VW_UpdateScreen();
+	handpic++;
+}
+
+/*
+==========================
+=
+= DialogFinish
+=
+==========================
+*/
+
+void DialogFinish(void)
+{
+	//this is empty
+}
+
+//==========================================================================
+
+/*
+==================
+=
+= StartDemoRecord
+=
+==================
+*/
+
+void StartDemoRecord(void)
+{
+	Sint16 level;
+	boolean esc;
+
+	VW_FixRefreshBuffer();
+	US_CenterWindow(30, 3);
+	PrintY += 6;
+	US_Print("  Record a demo from level(0-21):");
+	VW_UpdateScreen();
+	esc = !US_LineInput(px, py, str, NULL, true, 2, 0);
+	if (!esc)
+	{
+		level = atoi(str);
+		if (level >= 0 && level <= 21)
+		{
+			gamestate.mapon = level;
+			playstate = ex_warped;
+			IN_StartDemoRecord(0x1000);
+		}
+	}
+}
+
+/*
+==================
+=
+= EndDemoRecord
+=
+==================
+*/
+
+void EndDemoRecord(void)
+{
+	Sint16 handle;
+	boolean esc;
+	char filename[] = "DEMO?."EXTENSION;
+
+	IN_StopDemo();
+	VW_FixRefreshBuffer();
+	US_CenterWindow(22, 3);
+	PrintY += 6;
+	US_Print("  Save as demo #(0-9):");
+	VW_UpdateScreen();
+	esc = !US_LineInput(px, py, str, NULL, true, 2, 0);
+	if (!esc && str[0] >= '0' && str[0] <= '9')
+	{
+		filename[4] = str[0];
+		handle = open(filename, O_BINARY|O_WRONLY|O_CREAT, S_IFREG|S_IREAD|S_IWRITE);
+		if (handle == -1)
+		{
+			Quit("EndDemoRecord:  Cannot write demo file!");
+		}
+		write(handle, &mapon, sizeof(mapon));
+		write(handle, &DemoOffset, sizeof(DemoOffset));
+		CA_FarWrite(handle, DemoBuffer, DemoOffset);
+		close(handle);
+	}
+	IN_FreeDemoBuffer();
+}
+
+//==========================================================================
+
+/*
+==========================
+=
+= HandleDeath
+=
+==========================
+*/
+
+void HandleDeath(void)
+{
+	Uint16 y, color, top, bottom, selection, w, h;
+
+	_fstrcpy(str, levelnames[mapon]);
+	SizeText(str, &w, &h);
+
+	memset(gamestate.keys, 0, sizeof(gamestate.keys));
+	gamestate.lives--;
+	if (gamestate.lives >= 0)
+	{
+		VW_FixRefreshBuffer();
+		US_CenterWindow(20, 8);
+		PrintY += 3;
+		US_CPrint("You didn't make it past");
+		top = PrintY+22;
+		if (h < 15)
+			PrintY += 4;
+		US_CPrint(str);
+		PrintY = top+2;
+		US_CPrint("Try Again");
+		PrintY += 4;
+		bottom = PrintY-2;
+		US_CPrint("Exit to "WORLDMAPNAME);
+
+		IN_ClearKeysDown();
+		selection = 0;
+		while (true)
+		{
+			if (selection)
+			{
+				y = bottom;
+			}
+			else
+			{
+				y = top;
+			}
+
+// draw select bar
+			if ((TimeCount / 16) & 1)
+			{
+				color = SECONDCOLOR;
+			}
+			else
+			{
+				color = FIRSTCOLOR;
+			}
+			VWB_Hlin(WindowX+4, WindowX+WindowW-4, y, color);
+			VWB_Hlin(WindowX+4, WindowX+WindowW-4, y+1, color);
+			VWB_Hlin(WindowX+4, WindowX+WindowW-4, y+12, color);
+			VWB_Hlin(WindowX+4, WindowX+WindowW-4, y+13, color);
+			VWB_Vlin(y+1, y+11, WindowX+4, color);
+			VWB_Vlin(y+1, y+11, WindowX+5, color);
+			VWB_Vlin(y+1, y+11, WindowX+WindowW-4, color);
+			VWB_Vlin(y+1, y+11, WindowX+WindowW-5, color);
+
+			VW_UpdateScreen();
+
+// erase select bar
+			VWB_Hlin(WindowX+4, WindowX+WindowW-4, y, WHITE);
+			VWB_Hlin(WindowX+4, WindowX+WindowW-4, y+1, WHITE);
+			VWB_Hlin(WindowX+4, WindowX+WindowW-4, y+12, WHITE);
+			VWB_Hlin(WindowX+4, WindowX+WindowW-4, y+13, WHITE);
+			VWB_Vlin(y+1, y+11, WindowX+4, WHITE);
+			VWB_Vlin(y+1, y+11, WindowX+5, WHITE);
+			VWB_Vlin(y+1, y+11, WindowX+WindowW-4, WHITE);
+			VWB_Vlin(y+1, y+11, WindowX+WindowW-5, WHITE);
+
+			if (LastScan == sc_Escape)
+			{
+				gamestate.mapon = 0;		// exit to world map
+				IN_ClearKeysDown();
+				return;
+			}
+
+			IN_ReadControl(0, &c);
+			if (c.button0 || c.button1 || LastScan == sc_Return || LastScan == sc_Space)
+			{
+				if (selection)
+					gamestate.mapon = 0;		// exit to world map
+				return;
+			}
+			if (c.yaxis == -1 || LastScan == sc_UpArrow)
+			{
+				selection = 0;
+			}
+			else if (c.yaxis == 1 || LastScan == sc_DownArrow)
+			{
+				selection = 1;
+			}
+		}
+	}
+}
+
+//==========================================================================
+
+/*
+============================
+=
+= GameLoop
+=
+= A game has just started (after the cinematic or load game)
+=
+============================
+*/
+
+void GameLoop(void)
+{
+	Uint16 temp;
+#ifdef KEEN6
+	Uint16 i;
+#endif
+
+#ifdef KEEN6
+	if (!storedemo)
+	{
+		if (!US_ManualCheck())
+		{
+			loadedgame = false;
+			restartgame = gd_Continue;
+			return;
+		}
+	}
+#endif
+
+	if (playstate == ex_loadedgame)
+	{
+		goto loaded;
+	}
+reset:
+	gamestate.difficulty = restartgame;
+	restartgame = gd_Continue;
+	do
+	{
+startlevel:
+		SetupGameLevel(true);
+		if (mmerror)
+		{
+			if (gamestate.mapon != 0)
+			{
+				mmerror = false;
+				US_CenterWindow(20, 8);
+				PrintY += 20;
+				US_CPrint("Insufficient memory\nto load level!");
+				VW_UpdateScreen();
+				IN_Ack();
+				gamestate.mapon = 0;		// exit to world map
+				SetupGameLevel(true);
+			}
+			if (mmerror)
+			{
+				Quit("GameLoop: Insufficient memory to load world map!");
+			}
+		}
+loaded:
+		keenkilled = false;
+		SD_WaitSoundDone();
+
+		PlayLoop();
+
+		if (playstate != ex_loadedgame)
+		{
+			memset(gamestate.keys, 0, sizeof(gamestate.keys));
+#ifdef KEEN5
+			gamestate.keycard = false;
+#endif
+		}
+		VW_FixRefreshBuffer();
+
+		if (tedlevel)
+		{
+			if (playstate == ex_loadedgame)
+			{
+				goto loaded;
+			}
+			else if (playstate == ex_died)
+			{
+				goto startlevel;
+			}
+			else
+			{
+				TEDDeath();
+			}
+		}
+
+		levelcompleted = -1;
+		switch (playstate)
+		{
+		case ex_resetgame:
+			goto reset;
+
+		case ex_loadedgame:
+			goto loaded;
+
+		case ex_died:
+			HandleDeath();
+			break;
+
+#if defined KEEN4
+		case ex_rescued:
+			if (mapon != 0)
+			{
+				SD_PlaySound(SND_LEVELDONE);
+			}
+			levelcompleted = mapon;
+			gamestate.leveldone[mapon] = true;
+			RescuedMember();
+			if (gamestate.rescued != 8)
+			{
+				gamestate.mapon = 0;
+			}
+			else
+			{
+				FreeGraphics();
+				RF_FixOfs();
+				VW_FixRefreshBuffer();
+				FinaleLayout();
+				CheckHighScore(gamestate.score, gamestate.rescued);
+				return;
+			}
+			break;
+
+#elif defined KEEN5
+		case ex_fusebroke:
+			SD_PlaySound(SND_LEVELDONE);
+			levelcompleted = mapon;
+			gamestate.leveldone[mapon] = ex_fusebroke;
+			FinishedFuse();
+			gamestate.mapon = 0;
+			break;
+
+		case ex_qedbroke:
+			FreeGraphics();
+			RF_FixOfs();
+			VW_FixRefreshBuffer();
+			FinaleLayout();
+			CheckHighScore(gamestate.score, 0);
+			return;
+
+#elif defined KEEN6
+		case ex_hook:
+			GotHook();
+			goto completed;
+
+		case ex_sandwich:
+			GotSandwich();
+			goto completed;
+
+		case ex_card:
+			GotPasscard();
+			goto completed;
+
+		case ex_molly:
+			FreeGraphics();
+			RF_FixOfs();
+			VW_FixRefreshBuffer();
+			FinaleLayout();
+			goto check_score;
+
+#endif
+		case ex_completed:
+		case ex_foot:
+		case ex_portout:
+completed:
+			if (mapon != 0)
+			{
+				SD_PlaySound(SND_LEVELDONE);
+				gamestate.mapon = 0;
+				levelcompleted = mapon;
+				gamestate.leveldone[mapon] = true;
+				if (storedemo && mapon == 2)
+				{
+					IN_ClearKeysDown();
+					return;
+				}
+			}
+			else
+			{
+#if GRMODE != CGAGR
+				temp = bufferofs;
+				bufferofs = displayofs;
+#endif
+				US_CenterWindow(26, 8);
+				PrintY += 25;
+				US_CPrint("One moment");
+#if GRMODE == CGAGR
+				VW_UpdateScreen();
+#else
+				bufferofs = temp;
+#endif
+			}
+			break;
+
+		case ex_abortgame:
+			IN_ClearKeysDown();
+			return;
+		}
+	} while (gamestate.lives >= 0);
+
+	GameOver();
+
+check_score:
+#if defined KEEN4
+	CheckHighScore(gamestate.score, gamestate.rescued);
+#else
+	temp = 0;
+#if defined KEEN6
+	for (i = 0; i < GAMELEVELS; i++)
+	{
+		if (gamestate.leveldone[i])
+			temp++;
+	}
+#endif
+	CheckHighScore(gamestate.score, temp);
+#endif
+}
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/CK_KEEN.C b/16/keen456/KEEN4-6/CK_KEEN.C
new file mode 100755
index 00000000..3cb12b9a
--- /dev/null
+++ b/16/keen456/KEEN4-6/CK_KEEN.C
@@ -0,0 +1,2509 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+/*
+CK_KEEN.C
+=========
+
+Contains the following actor types (in this order):
+
+- Keen (regular levels)
+
+*/
+
+#include "CK_DEF.H"
+
+/*
+=============================================================================
+
+						 GLOBAL VARIABLES
+
+=============================================================================
+*/
+
+Sint16 singlegravity;	// left over from Keen Dreams, not used in Keen 4-6
+
+Uint16 bounceangle [8][8] =
+{
+	{ 0,  0,  0,  0,  0,  0,  0,  0},
+	{ 7,  6,  5,  4,  3,  2,  1,  0},
+	{ 5,  4,  3,  2,  1,  0, 15, 14},
+	{ 5,  4,  3,  2,  1,  0, 15, 14},
+	{ 3,  2,  1,  0, 15, 14, 13, 12},
+	{ 9,  8,  7,  6,  5,  4,  3,  2},
+	{ 9,  8,  7,  6,  5,  4,  3,  2},
+	{11, 10,  9,  8,  7,  6,  5,  4}
+};
+
+#ifndef KEEN4
+arrowdirtype arrowflip[] = {arrow_South, arrow_West, arrow_North, arrow_East, arrow_SouthWest, arrow_NorthWest, arrow_NorthEast, arrow_SouthEast};
+#endif
+
+statetype s_keenstand     = {KEENSTANDLSPR, KEENSTANDRSPR, stepthink, false, true, 4, 0, 32, KeenPauseThink, KeenContact, KeenStandReact, &s_keenstand};
+
+#ifdef KEEN5
+statetype s_keenride     = {KEENONPLATSPR, KEENONPLATSPR, stepthink, false, true, 4, 0, 32, KeenStandThink, KeenContact, KeenStandReact, &s_keenride};
+#endif
+
+statetype s_keenpauselook = {KEENLOOKUSPR, KEENLOOKUSPR, stepthink, false, true, 60, 0, 0, KeenPauseThink, KeenContact, KeenStandReact, &s_keenstand};
+
+statetype s_keenwait1    = {KEENWAITR2SPR, KEENWAITR2SPR, stepthink, false, true, 90, 0, 0, KeenPauseThink, KeenContact, KeenStandReact, &s_keenwait2};
+statetype s_keenwait2    = {KEENWAITR1SPR, KEENWAITR1SPR, stepthink, false, true, 10, 0, 0, KeenPauseThink, KeenContact, KeenStandReact, &s_keenwait3};
+statetype s_keenwait3    = {KEENWAITR2SPR, KEENWAITR2SPR, stepthink, false, true, 90, 0, 0, KeenPauseThink, KeenContact, KeenStandReact, &s_keenwait4};
+statetype s_keenwait4    = {KEENWAITR1SPR, KEENWAITR1SPR, stepthink, false, true, 10, 0, 0, KeenPauseThink, KeenContact, KeenStandReact, &s_keenwait5};
+statetype s_keenwait5    = {KEENWAITR2SPR, KEENWAITR2SPR, stepthink, false, true, 90, 0, 0, KeenPauseThink, KeenContact, KeenStandReact, &s_keenwait6};
+statetype s_keenwait6    = {KEENWAITR3SPR, KEENWAITR3SPR, stepthink, false, true, 70, 0, 0, KeenPauseThink, KeenContact, KeenStandReact, &s_keenstand};
+
+#ifdef KEEN4
+statetype s_keenmoon1     = {KEENMOON1SPR, KEENMOON1SPR, stepthink, false, true, 20, 0, 0, KeenPauseThink, KeenContact, KeenStandReact, &s_keenmoon2};
+statetype s_keenmoon2     = {KEENMOON2SPR, KEENMOON2SPR, stepthink, false, true, 90, 0, 0, KeenPauseThink, KeenContact, KeenStandReact, &s_keenmoon3};
+statetype s_keenmoon3     = {KEENMOON1SPR, KEENMOON1SPR, stepthink, false, true, 20, 0, 0, KeenPauseThink, KeenContact, KeenStandReact, &s_keenstand};
+#endif
+
+statetype s_keenread      = {KEENSITREAD1SPR, KEENSITREAD1SPR, step, false, true, 16, 0, 0, 0, KeenContact, KeenStandReact, &s_keenread2};
+statetype s_keenread2     = {KEENSITREAD2SPR, KEENSITREAD2SPR, step, false, true, 16, 0, 0, 0, KeenContact, KeenStandReact, &s_keenread3};
+statetype s_keenread3     = {KEENSITREAD3SPR, KEENSITREAD3SPR, step, false, true, 16, 0, 0, 0, KeenContact, KeenStandReact, &s_keenread4};
+statetype s_keenread4     = {KEENSITREAD4SPR, KEENSITREAD4SPR, step, false, true, 16, 0, 0, 0, KeenContact, KeenStandReact, &s_keenread5};
+statetype s_keenread5     = {KEENREAD1SPR, KEENREAD1SPR, stepthink, false, true, 300, 0, 0, KeenReadThink, KeenContact, KeenStandReact, &s_keenread6};
+statetype s_keenread6     = {KEENREAD2SPR, KEENREAD2SPR, stepthink, false, true, 16, 0, 0, KeenReadThink, KeenContact, KeenStandReact, &s_keenread7};
+statetype s_keenread7     = {KEENREAD3SPR, KEENREAD3SPR, stepthink, false, true, 16, 0, 0, KeenReadThink, KeenContact, KeenStandReact, &s_keenread5};
+statetype s_keenstopread  = {KEENSTOPREAD1SPR, KEENSTOPREAD1SPR, step, false, true, 12, 0, 0, 0, KeenContact, KeenStandReact, &s_keenstopread2};
+statetype s_keenstopread2 = {KEENSTOPREAD2SPR, KEENSTOPREAD2SPR, step, false, true, 12, 0, 0, 0, KeenContact, KeenStandReact, &s_keenstopread3};
+statetype s_keenstopread3 = {KEENSITREAD2SPR, KEENSITREAD2SPR, step, false, true, 12, 0, 0, 0, KeenContact, KeenStandReact, &s_keenstand};
+
+statetype s_keenlookup    = {KEENLOOKUSPR, KEENLOOKUSPR, stepthink, false, true, 30, 0, 0, KeenLookUpThink, KeenContact, KeenStandReact, &s_keenlookup2};
+statetype s_keenlookup2   = {KEENLOOKUSPR, KEENLOOKUSPR, think, false, true, 0, 0, 0, KeenLookUpThink, KeenPosContact, KeenStandReact, NULL};
+
+statetype s_keenlookdown  = {KEENLOOKD1SPR, KEENLOOKD1SPR, stepthink, false, true, 6, 0, 0, KeenLookDownThink, KeenContact, KeenStandReact, &s_keenlookdown2};
+statetype s_keenlookdown2 = {KEENLOOKD2SPR, KEENLOOKD2SPR, stepthink, false, true, 24, 0, 0, KeenLookDownThink, KeenPosContact, KeenStandReact, &s_keenlookdown3};
+statetype s_keenlookdown3 = {KEENLOOKD2SPR, KEENLOOKD2SPR, think, false, true, 0, 0, 0, KeenLookDownThink, KeenPosContact, KeenStandReact, NULL};
+statetype s_keenlookdown4 = {KEENLOOKD1SPR, KEENLOOKD1SPR, step, false, true, 6, 0, 0, 0, KeenContact, KeenStandReact, &s_keenstand};
+
+statetype s_keendrop   = {KEENLOOKD1SPR, KEENLOOKD1SPR, step, false, false, 0, 0, 0, KeenDropDownThink, KeenContact, KeenSimpleReact, &s_keenjump3};
+statetype s_keendead   = {-1, -1, think, false, false, 10, 0, 0, 0, 0, R_Draw, NULL};
+
+statetype s_keendie1     = {KEENDIE1SPR, KEENDIE1SPR, think, false, false, 100, 0, 0, KeenDieThink, 0, R_Draw, &s_keendie1};
+statetype s_keendie2     = {KEENDIE2SPR, KEENDIE2SPR, think, false, false, 100, 0, 0, KeenDieThink, 0, R_Draw, &s_keendie2};
+
+#ifdef KEEN4
+statetype s_keensuitdie1 = {SCUBAKEENDEAD1SPR, SCUBAKEENDEAD1SPR, think, false, false, 100, 0, 0, KeenDieThink, NULL, R_Draw, &s_keensuitdie1};
+statetype s_keensuitdie2 = {SCUBAKEENDEAD2SPR, SCUBAKEENDEAD2SPR, think, false, false, 100, 0, 0, KeenDieThink, NULL, R_Draw, &s_keensuitdie2};
+#endif
+
+statetype s_keenshoot1    = {KEENSHOOTLSPR, KEENSHOOTRSPR, step, false, true, 9, 0, 0, KeenShootThink, KeenContact, KeenStandReact, &s_keenshoot2};
+statetype s_keenshoot2    = {KEENSHOOTLSPR, KEENSHOOTRSPR, step, false, true, 6, 0, 0, 0, KeenContact, KeenStandReact, &s_keenstand};
+
+statetype s_keenshootup1  = {KEENSHOOTUSPR, KEENSHOOTUSPR, step, false, true, 9, 0, 0, KeenShootThink, KeenContact, KeenStandReact, &s_keenshootup2};
+statetype s_keenshootup2  = {KEENSHOOTUSPR, KEENSHOOTUSPR, step, false, true, 6, 0, 0, 0, KeenContact, KeenStandReact, &s_keenlookup};
+
+statetype s_keenswitch  = {KEENENTER1SPR, KEENENTER1SPR, step, false, true, 8, 0, 0, KeenSwitchThink, NULL, KeenStandReact, &s_keenswitch2};
+statetype s_keenswitch2 = {KEENENTER1SPR, KEENENTER1SPR, step, false, true, 8, 0, 0, 0, 0, KeenStandReact, &s_keenstand};
+statetype s_keenkey     = {KEENENTER1SPR, KEENENTER1SPR, step, false, true, 6, 0, 0, KeenKeyThink, NULL, KeenStandReact, &s_keenswitch2};
+
+statetype s_keenlineup  = {KEENENTER1SPR, KEENENTER1SPR, think, false, false, 0, 0, 0, T_LineUp, 0, R_Draw, NULL};
+#ifdef KEEN5
+statetype s_keenenter0   = {KEENENTER1SPR, KEENENTER1SPR, step, false, false, 45, 0, -64, NULL, NULL, R_Draw, &s_keenenter1};
+statetype s_keenteleport = {KEENWAITR2SPR, KEENWAITR2SPR, think, false, false, 0, 0, 0, NULL, NULL, R_Draw, NULL};
+#endif
+
+statetype s_keenenter1 = {KEENENTER1SPR, KEENENTER1SPR, step, false, false, 9, 0, -64, WalkSound1, NULL, R_Draw, &s_keenenter2};
+statetype s_keenenter2 = {KEENENTER2SPR, KEENENTER2SPR, step, false, false, 9, 0, -64, WalkSound2, NULL, R_Draw, &s_keenenter3};
+statetype s_keenenter3 = {KEENENTER3SPR, KEENENTER3SPR, step, false, false, 9, 0, -64, WalkSound1, NULL, R_Draw, &s_keenenter4};
+statetype s_keenenter4 = {KEENENTER4SPR, KEENENTER4SPR, step, false, false, 9, 0, -64, WalkSound2, NULL, R_Draw, &s_keenenter5};
+statetype s_keenenter5 = {KEENENTER5SPR, KEENENTER5SPR, step, false, false, 9, 0, -64, KeenEnterThink, NULL, R_Draw, &s_keenstand};
+#ifdef KEEN5
+statetype s_keenenter6 = {-1, -1, step, false, false, 9, 0, -64, KeenEnterThink, 0, R_Draw, &s_keenstand};
+#endif
+
+statetype s_keenpole      = {KEENSHINNYL1SPR, KEENSHINNYR1SPR, think, false, false, 0, 0, 0, KeenPoleThink, KeenPosContact, KeenSimpleReact, &s_keenpole};
+
+statetype s_keenclimb1 = {KEENSHINNYL1SPR, KEENSHINNYR1SPR, slidethink, false, false, 8, 0, 8, KeenClimbThink, KeenPosContact, KeenSimpleReact, &s_keenclimb2};
+statetype s_keenclimb2 = {KEENSHINNYL2SPR, KEENSHINNYR2SPR, slidethink, false, false, 8, 0, 8, KeenClimbThink, KeenPosContact, KeenSimpleReact, &s_keenclimb3};
+statetype s_keenclimb3 = {KEENSHINNYL3SPR, KEENSHINNYR3SPR, slidethink, false, false, 8, 0, 8, KeenClimbThink, KeenPosContact, KeenSimpleReact, &s_keenclimb1};
+
+statetype s_keenslide1 = {KEENSLIDED1SPR, KEENSLIDED1SPR, slide, false, false, 8, 0, 24, KeenDropThink, KeenPosContact, KeenPoleReact, &s_keenslide2};
+statetype s_keenslide2 = {KEENSLIDED2SPR, KEENSLIDED2SPR, slide, false, false, 8, 0, 24, KeenDropThink, KeenPosContact, KeenPoleReact, &s_keenslide3};
+statetype s_keenslide3 = {KEENSLIDED3SPR, KEENSLIDED3SPR, slide, false, false, 8, 0, 24, KeenDropThink, KeenPosContact, KeenPoleReact, &s_keenslide4};
+statetype s_keenslide4 = {KEENSLIDED4SPR, KEENSLIDED4SPR, slide, false, false, 8, 0, 24, KeenDropThink, KeenPosContact, KeenPoleReact, &s_keenslide1};
+
+statetype s_keenpoleshoot1 = {KEENPSHOOTLSPR, KEENPSHOOTRSPR, step, false, false, 9, 0, 0, KeenShootThink, KeenPosContact, KeenSimpleReact, &s_keenpoleshoot2};
+statetype s_keenpoleshoot2 = {KEENPSHOOTLSPR, KEENPSHOOTRSPR, step, false, false, 6, 0, 0, 0, KeenPosContact, KeenSimpleReact, &s_keenpole};
+
+statetype s_keenpoleshootup1 = {KEENPLSHOOTUSPR, KEENPRSHOOTUSPR, step, false, false, 9, 0, 0, KeenShootThink, KeenPosContact, KeenSimpleReact, &s_keenpoleshootup2};
+statetype s_keenpoleshootup2 = {KEENPLSHOOTUSPR, KEENPRSHOOTUSPR, step, false, false, 6, 0, 0, 0, KeenPosContact, KeenSimpleReact, &s_keenpole};
+
+statetype s_keenpoleshootdown1 = {KEENPLSHOOTDSPR, KEENPRSHOOTDSPR, step, false, false, 9, 0, 0, KeenShootThink, KeenPosContact, KeenSimpleReact, &s_keenpoleshootdown2};
+statetype s_keenpoleshootdown2 = {KEENPLSHOOTDSPR, KEENPRSHOOTDSPR, step, false, false, 6, 0, 0, 0, KeenPosContact, KeenSimpleReact, &s_keenpole};
+
+statetype s_keenwalk1     = {KEENRUNL1SPR, KEENRUNR1SPR, slidethink, true, true, 6, 24, 0, KeenWalkThink, KeenContact, KeenWalkReact, &s_keenwalk2};
+statetype s_keenwalk2     = {KEENRUNL2SPR, KEENRUNR2SPR, slidethink, true, true, 6, 24, 0, KeenWalkThink, KeenContact, KeenWalkReact, &s_keenwalk3};
+statetype s_keenwalk3     = {KEENRUNL3SPR, KEENRUNR3SPR, slidethink, true, true, 6, 24, 0, KeenWalkThink, KeenContact, KeenWalkReact, &s_keenwalk4};
+statetype s_keenwalk4     = {KEENRUNL4SPR, KEENRUNR4SPR, slidethink, true, true, 6, 24, 0, KeenWalkThink, KeenContact, KeenWalkReact, &s_keenwalk1};
+
+statetype s_keenpogodown  = {KEENPOGOL2SPR, KEENPOGOR2SPR, step, true, false, 1, 0, 0, KeenBounceThink, KeenContact, KeenPogoReact, &s_keenpogo};
+statetype s_keenpogo      = {KEENPOGOL2SPR, KEENPOGOR2SPR, think, true, false, 0, 0, 0, KeenPogoThink, KeenContact, KeenPogoReact, &s_keenpogo2};
+statetype s_keenpogo2     = {KEENPOGOL1SPR, KEENPOGOR1SPR, think, true, false, 0, 0, 0, KeenPogoThink, KeenContact, KeenPogoReact, NULL};
+
+statetype s_keenjump1     = {KEENJUMPL1SPR, KEENJUMPR1SPR, think, false, false, 0, 0, 0, KeenAirThink, KeenContact, KeenAirReact, &s_keenjump2};
+statetype s_keenjump2     = {KEENJUMPL2SPR, KEENJUMPR2SPR, think, false, false, 0, 0, 0, KeenAirThink, KeenContact, KeenAirReact, &s_keenjump3};
+statetype s_keenjump3     = {KEENJUMPL3SPR, KEENJUMPR3SPR, stepthink, false, false, 50, 0, 0, KeenAirThink, KeenContact, KeenAirReact, &s_keenjump4};
+statetype s_keenjump4     = {KEENJUMPL2SPR, KEENJUMPR2SPR, stepthink, false, false, 40, 0, 0, KeenAirThink, KeenContact, KeenAirReact, &s_keenjump3};
+
+statetype s_keenairshoot1 = {KEENJLSHOOTLSPR, KEENJRSHOOTRSPR, stepthink, false, false, 9, 0, 0, T_Projectile, KeenContact, KeenAirReact, &s_keenairshoot2};
+statetype s_keenairshoot2 = {KEENJLSHOOTLSPR, KEENJRSHOOTRSPR, stepthink, true, false, 1, 0, 0, KeenShootThink, KeenContact, KeenAirReact, &s_keenairshoot3};
+statetype s_keenairshoot3 = {KEENJLSHOOTLSPR, KEENJRSHOOTRSPR, stepthink, false, false, 6, 0, 0, T_Projectile, KeenContact, KeenAirReact, &s_keenjump3};
+
+statetype s_keenairshootup1 = {KEENJSHOOTUSPR, KEENJSHOOTUSPR, stepthink, false, false, 9, 0, 0, T_Projectile, KeenContact, KeenAirReact, &s_keenairshootup2};
+statetype s_keenairshootup2 = {KEENJSHOOTUSPR, KEENJSHOOTUSPR, stepthink, true, false, 1, 0, 0, KeenShootThink, KeenContact, KeenAirReact, &s_keenairshootup3};
+statetype s_keenairshootup3 = {KEENJSHOOTUSPR, KEENJSHOOTUSPR, stepthink, false, false, 6, 0, 0, T_Projectile, KeenContact, KeenAirReact, &s_keenjump3};
+
+statetype s_keenairshootdown1 = {KEENJSHOOTDSPR, KEENJSHOOTDSPR, stepthink, false, false, 9, 0, 0, T_Projectile, KeenContact, KeenAirReact, &s_keenairshootdown2};
+statetype s_keenairshootdown2 = {KEENJSHOOTDSPR, KEENJSHOOTDSPR, stepthink, true, false, 1, 0, 0, KeenShootThink, KeenContact, KeenAirReact, &s_keenairshootdown3};
+statetype s_keenairshootdown3 = {KEENJSHOOTDSPR, KEENJSHOOTDSPR, stepthink, false, false, 6, 0, 0, T_Projectile, KeenContact, KeenAirReact, &s_keenjump3};
+
+statetype s_keenholdon  = {KEENHANGLSPR, KEENHANGRSPR, step, false, false, 12, 0, 0, 0, KeenPosContact, KeenSimpleReact, &s_keenholdon2};
+statetype s_keenholdon2 = {KEENHANGLSPR, KEENHANGRSPR, think, false, false, 0, 0, 0, KeenHoldThink, KeenPosContact, KeenSimpleReact, NULL};
+
+statetype s_keenclimbup  = {KEENCLIMBEDGEL1SPR, KEENCLIMBEDGER1SPR, step, false, false, 10, 0, 0, T_PullUp1, KeenPosContact, KeenSimpleReact, &s_keenclimbup2};
+statetype s_keenclimbup2 = {KEENCLIMBEDGEL2SPR, KEENCLIMBEDGER2SPR, step, false, false, 10, 0, 0, T_PullUp2, KeenPosContact, KeenSimpleReact, &s_keenclimbup3};
+statetype s_keenclimbup3 = {KEENCLIMBEDGEL3SPR, KEENCLIMBEDGER3SPR, step, false, false, 10, 0, 0, T_PullUp3, KeenPosContact, KeenSimpleReact, &s_keenclimbup4};
+statetype s_keenclimbup4 = {KEENCLIMBEDGEL4SPR, KEENCLIMBEDGER4SPR, step, false, false, 10, 0, 0, T_PulledUp, KeenPosContact, KeenSimpleReact, &s_keenclimbup5};
+statetype s_keenclimbup5 = {KEENSTANDLSPR, KEENSTANDRSPR, step, false, false, 6, 0, 0, 0, KeenPosContact, KeenSimpleReact, &s_keenstand};
+
+Sint16 slopespeed[8] = {0, 0, 4, 4, 8, -4, -4, -8};
+Sint16 polexspeed[3] = {-8, 0, 8};
+
+Sint16 shotsinclip[4] = {0, 8, 5, 5};
+Sint16 bonussound[] = {
+	SND_GETKEY,SND_GETKEY,SND_GETKEY,SND_GETKEY,
+	SND_GETPOINTS,SND_GETPOINTS,SND_GETPOINTS,
+	SND_GETPOINTS,SND_GETPOINTS,SND_GETPOINTS,
+	SND_EXTRAKEEN,
+	SND_GETAMMO
+#ifdef KEEN5
+	,SND_GETKEYCARD
+#endif
+};
+Sint16 bonuspoints[] = {
+	0, 0, 0, 0,
+	100, 200, 500,
+	1000, 2000, 5000,
+	0,
+	0
+#ifdef KEEN5
+	,0
+#endif
+};
+Sint16 bonussprite[] = {
+	BONUSGEMSPR, BONUSGEMSPR, BONUSGEMSPR, BONUSGEMSPR,
+	BONUS100SPR, BONUS200SPR, BONUS500SPR,
+	BONUS1000SPR, BONUS2000SPR, BONUS5000SPR,
+	BONUS1UPSPR,
+	BONUSCLIPSPR
+#ifdef KEEN5
+	,BONUSCARDSPR
+#endif
+};
+
+Uint16 zeromap = 0;
+
+// uninitialized variables:
+
+/*
+=============================================================================
+
+						 LOCAL VARIABLES
+
+=============================================================================
+*/
+
+Sint16 jumptime;
+Sint32 leavepoletime;
+Sint16 moonok;
+
+/*
+=============================================================================
+
+								KEEN
+
+player->temp1 = pausetime / pointer to zees when sleeping
+player->temp2 = pausecount / stagecount
+player->temp3 =
+player->temp4 =
+
+=============================================================================
+*/
+
+
+/*
+===============
+=
+= SpawnKeen
+=
+===============
+*/
+
+void SpawnKeen(Sint16 x, Sint16 y, Sint16 dir)
+{
+	player->obclass = keenobj;
+	player->active = ac_allways;
+	player->priority = 1;
+	player->x = CONVERT_TILE_TO_GLOBAL(x);
+	player->y = CONVERT_TILE_TO_GLOBAL(y) - 0xF1;	//TODO: weird
+
+	player->xdir = dir;
+	player->ydir = 1;
+	NewState(player, &s_keenstand);
+}
+
+//==========================================================================
+
+/*
+======================
+=
+= CheckGrabPole
+=
+======================
+*/
+
+boolean CheckGrabPole(objtype *ob)
+{
+	Uint16 far *map;
+
+//
+// kludgy bit to not let you grab a pole the instant you jump off it
+//
+	if (lasttimecount < leavepoletime)
+	{
+		leavepoletime = 0;
+	}
+	else if (lasttimecount-leavepoletime < 19)
+	{
+		return false;
+	}
+
+	if (c.yaxis == -1)
+	{
+		map = mapsegs[1] + mapbwidthtable[(ob->top+6*PIXGLOBAL)/TILEGLOBAL]/2;
+	}
+	else
+	{
+		map = mapsegs[1] + mapbwidthtable[ob->tilebottom+1]/2;
+	}
+
+	map += ob->tilemidx;
+
+	if ((tinf[INTILE + *map] & 0x7F) == INTILE_POLE)
+	{
+		ob->x = CONVERT_TILE_TO_GLOBAL(ob->tilemidx-1) + 8*PIXGLOBAL;
+		xtry = 0;
+		ytry = c.yaxis * 32;
+		ob->needtoclip = cl_noclip;		// can climb through pole holes
+		ob->state = &s_keenpole;
+		return true;
+	}
+	return false;
+}
+
+//==========================================================================
+
+/*
+======================
+=
+= CheckEnterHouse
+=
+= Checks for tiles that Keen can interact with by pressing up
+=
+======================
+*/
+
+boolean CheckEnterHouse(objtype *ob)
+{
+	Uint16 temp;
+#ifdef KEEN5
+	Uint16 infoval;
+#endif
+	Uint16 intile, intile2;
+
+	intile = tinf[INTILE + *(mapsegs[1]+mapbwidthtable[ob->tiletop]/2+ob->tilemidx)];
+	if (intile == INTILE_SWITCH0 || intile == INTILE_SWITCH1 || intile == INTILE_BRIDGESWITCH)
+	{
+		temp = CONVERT_TILE_TO_GLOBAL(ob->tilemidx) - 4*PIXGLOBAL;
+		if (ob->x != temp)
+		{
+			ob->temp1 = temp;
+			ob->state = &s_keenlineup;
+		}
+		else
+		{
+			ob->state = &s_keenswitch;
+		}
+		upheld = true;
+		return true;
+	}
+	else if (intile == INTILE_DOOR || intile == INTILE_KEYCARDDOOR)
+	{
+		temp = CONVERT_TILE_TO_GLOBAL(ob->tilemidx) + 6*PIXGLOBAL;
+		intile2 = tinf[INTILE + *(mapsegs[1]+mapbwidthtable[ob->tiletop]/2+ob->tilemidx-1)];
+		if (intile2 == 2 || intile2 == 32)
+			temp -= TILEGLOBAL;
+
+		// BUG:
+		//
+		// The s_keenenter? states rely on Keen's ydir being set to 1,
+		// which may not always be the case (e.g. if Keen was pushed off
+		// a pole by another actor in the level).
+		// If ydir is not 1, Keen will not move up during that animation
+		// which means the teleport coordinates won't be read from the
+		// intended tile position and Keen might end up teleporting to
+		// position 0, 0 in the map and thus win the current level.
+		// 
+		// That can easily be avoided by setting ob->ydir to 1 when
+		// changing ob->state to s_keenenter0 or s_keenenter1.
+
+		if (ob->x != temp)
+		{
+			ob->temp1 = temp;
+			ob->state = &s_keenlineup;
+		}
+#ifdef KEEN5
+		else if (intile == INTILE_KEYCARDDOOR)
+		{
+			if (gamestate.keycard)
+			{
+				gamestate.keycard = false;
+				SD_PlaySound(SND_OPENCARDDOOR);
+				GetNewObj(false);
+				new->x = ob->tilemidx - 2;
+				new->y = ob->tilebottom - 4;
+				new->active = ac_allways;
+				new->needtoclip = cl_noclip;
+				new->obclass = inertobj;
+				NewState(new, &s_carddoor);
+				// Note: no invincibility here - card doors were always used as level exits in Keen 5
+				ob->state = &s_keenenter0;
+				ob->priority = 0;
+				upheld = true;
+				return true;
+			}
+			else
+			{
+				SD_PlaySound(SND_NOWAY);
+				ob->state = &s_keenstand;
+				upheld = true;
+				return false;
+			}
+		}
+#endif
+		else
+		{
+			invincible = 110;	//about 1.57 seconds
+			ob->state = &s_keenenter1;
+			ob->priority = 0;
+#ifdef KEEN5
+			{
+				infoval = *(mapsegs[2]+mapbwidthtable[ob->tiletop]/2+ob->tilemidx);
+				if (!infoval)
+					SpawnTeleport();
+			}
+#endif
+		}
+		upheld = true;
+		return true;
+	}
+	return false;
+}
+
+//==========================================================================
+
+/*
+============================
+=
+= WalkSound1
+=
+============================
+*/
+
+void WalkSound1(objtype *ob)
+{
+	SD_PlaySound(SND_WORLDWALK1);
+	ob++;			// shut up compiler
+}
+
+/*
+============================
+=
+= WalkSound2
+=
+============================
+*/
+
+void WalkSound2(objtype *ob)
+{
+	SD_PlaySound(SND_WORLDWALK2);
+	ob++;			// shut up compiler
+}
+
+//==========================================================================
+
+/*
+============================
+=
+= KeenStandThink
+=
+============================
+*/
+
+void KeenStandThink(objtype *ob)
+{
+#ifdef KEEN5
+	if (ob->hitnorth == 25 && ob->state != &s_keenride)
+	{
+		ob->state = &s_keenride;
+	}
+#endif
+
+	if (c.xaxis)
+	{
+	// started walking
+		ob->state = &s_keenwalk1;
+		KeenWalkThink(ob);
+		xtry = (Sint16)(ob->xdir * ob->state->xmove * tics) / 4;
+	}
+	else if (firebutton && !fireheld)
+	{
+	// shoot current xdir
+		fireheld = true;
+		if (c.yaxis == -1)
+		{
+			ob->state = &s_keenshootup1;
+		}
+		else
+		{
+			ob->state = &s_keenshoot1;
+		}
+	}
+	else if (jumpbutton && ! jumpheld)
+	{
+	// jump straight up
+		jumpheld = true;
+		SD_PlaySound(SND_JUMP);
+		ob->xspeed = 0;
+		ob->yspeed = -40;
+		ytry = 0;
+		jumptime = 18;
+		ob->state = &s_keenjump1;
+	}
+	else if (pogobutton && !pogoheld)
+	{
+	// get on pogo
+		pogoheld = true;
+		SD_PlaySound(SND_JUMP);
+		ob->state = &s_keenpogodown;
+		ob->xspeed = 0;
+		ob->yspeed = -48;
+		ytry = 0;
+		jumptime = 24;
+	}
+	else
+	{
+		switch (c.yaxis)
+		{
+		case -1:
+			if (CheckGrabPole(ob))
+				break;
+			if (upheld || !CheckEnterHouse(ob))
+			{
+				ob->state = &s_keenlookup;
+			}
+			break;
+		case 1:
+			if (CheckGrabPole(ob))
+				break;
+			ob->state = &s_keenlookdown;
+		}
+		return;
+	}
+}
+
+//===========================================================================
+
+/*
+=======================
+=
+= KeenPauseThink
+=
+= Do special animations in time
+=
+=======================
+*/
+
+void KeenPauseThink(objtype *ob)
+{
+#ifdef KEEN5
+	if (ob->hitnorth == 25 && ob->state != &s_keenride)
+	{
+		ob->state = &s_keenride;
+	}
+#endif
+
+	if (c.dir != dir_None || jumpbutton || pogobutton || firebutton)
+	{
+		ob->temp1 = ob->temp2 = 0;			// not paused any more
+		ob->state = &s_keenstand;
+		KeenStandThink(ob);
+	}
+	else
+	{
+		//only increase idle counter when NOT standing on a sprite:
+		if ((ob->hitnorth & ~7) != 0x18)
+			ob->temp1 = ob->temp1 + tics;
+
+		switch (ob->temp2)
+		{
+		case 0:
+			if (ob->temp1 > 200)
+			{
+				ob->temp2++;
+				ob->state = &s_keenpauselook;
+				ob->temp1 = 0;
+			}
+			break;
+		case 1:
+			if (ob->temp1 > 300)
+			{
+				ob->temp2++;
+				ob->temp1 = 0;
+#ifdef KEEN4
+				if (moonok == 1)
+				{
+					moonok = 2;	//don't moon again unless the level is restarted
+					ob->state = &s_keenmoon1;
+				}
+				else
+#endif
+				{
+					ob->state = &s_keenwait1;
+				}
+			}
+			break;
+		case 2:
+			if (ob->temp1 > 700)
+			{
+				ob->temp2++;
+				ob->state = &s_keenread;
+				ob->temp1 = 0;
+			}
+			break;
+		}
+	}
+}
+
+//===========================================================================
+
+/*
+=======================
+=
+= KeenReadThink
+=
+=======================
+*/
+
+void KeenReadThink(objtype *ob)
+{
+	if (storedemo)
+	{
+		playstate = ex_abortgame;
+		IN_ClearKeysDown();
+	}
+	if (c.dir != dir_None || jumpbutton || pogobutton)
+	{
+		ob->temp1 = ob->temp2 = 0;
+		ob->state = &s_keenstopread;
+	}
+}
+
+//===========================================================================
+
+/*
+=======================
+=
+= KeenLookUpThink
+=
+=======================
+*/
+
+void KeenLookUpThink(objtype *ob)
+{
+	if (c.yaxis != -1 || c.xaxis
+		|| (jumpbutton && !jumpheld)
+		|| (pogobutton && !pogoheld)
+		|| firebutton)
+	{
+		ob->state = &s_keenstand;
+		KeenStandThink(ob);
+	}
+}
+
+//===========================================================================
+
+/*
+=======================
+=
+= KeenLookDownThink
+=
+=======================
+*/
+
+void KeenLookDownThink(objtype *ob)
+{
+	Uint16 far *map;
+	Sint16 y, ymove;
+	Uint16 tile;
+
+	if (jumpbutton && ! jumpheld && (ob->hitnorth & 7) == 1)
+	{
+	//
+	// drop down a level
+	//
+		jumpheld = true;
+
+		y = ob->tilebottom;
+		map = (Uint16 far *)mapsegs[1] + mapbwidthtable[y]/2 + ob->tilemidx;
+		tile = *map;
+		if (tinf[WESTWALL+tile] || tinf[EASTWALL+tile] || tinf[SOUTHWALL+tile])
+			return;				// wall prevents drop down
+
+		map += mapwidth;
+		tile = *map;
+		if (tinf[WESTWALL+tile] || tinf[EASTWALL+tile] || tinf[SOUTHWALL+tile])
+			return;				// wall prevents drop down
+
+		ymove = max(4, tics) * PIXGLOBAL;
+		if (gamestate.riding)
+			ymove += gamestate.riding->ymove;
+		ob->bottom += ymove;
+		gamestate.riding = NULL;
+		ob->y += ymove;
+		xtry = ytry = 0;
+		ob->state = &s_keenjump3;
+		ob->xspeed = ob->yspeed = 0;
+		SD_PlaySound(SND_PLUMMET);
+	}
+	else if (c.yaxis != 1 || c.xaxis
+		|| (jumpbutton && !jumpheld)
+		|| (pogobutton && !pogoheld))
+	{
+		ob->state = &s_keenlookdown4;
+	}
+}
+
+//===========================================================================
+
+/*
+=======================
+=
+= KeenWalkThink
+=
+=======================
+*/
+
+void KeenWalkThink(objtype *ob)
+{
+	Sint16 xmove;
+
+	if (c.xaxis == 0)
+	{
+	//
+	// stopped running
+	//
+		ob->state = &s_keenstand;
+		KeenStandThink(ob);
+		return;
+	}
+
+	ob->xdir = c.xaxis;
+
+	switch (c.yaxis)
+	{
+	case -1:
+		if (CheckGrabPole(ob))
+			return;
+		if (upheld)
+			return;
+		if (!CheckEnterHouse(ob))
+			break;;
+		return;
+
+	case 1:
+		if (!CheckGrabPole(ob))
+			break;
+		return;
+	}
+
+	if (firebutton && !fireheld)
+	{
+	//
+	// shoot
+	//
+		fireheld = true;
+		if (c.yaxis == -1)
+		{
+			ob->state = &s_keenshootup1;
+		}
+		else
+		{
+			ob->state = &s_keenshoot1;
+		}
+		return;
+	}
+
+	if (jumpbutton && !jumpheld)
+	{
+	//
+	// running jump
+	//
+		jumpheld = true;
+		SD_PlaySound(SND_JUMP);
+		ob->xspeed = ob->xdir * 16;
+		ob->yspeed = -40;
+		xtry = ytry = 0;
+		jumptime = 18;
+		ob->state = &s_keenjump1;
+	}
+
+	if (pogobutton && !pogoheld)
+	{
+	//
+	// get on pogo
+	//
+		pogoheld = true;
+		ob->state = &s_keenpogodown;
+		SD_PlaySound(SND_JUMP);
+		ob->xspeed = ob->xdir * 16;
+		ob->yspeed = -48;
+		xtry = 0;
+		jumptime = 24;
+		return;
+	}
+
+	//
+	// give speed for slopes
+	//
+	xmove = slopespeed[ob->hitnorth & 7] * tics;
+	xtry += xmove;
+
+	//
+	// handle walking sounds
+	//
+	if (ob->state == &s_keenwalk1 && ob->temp3 == 0)
+	{
+		SD_PlaySound(SND_WORLDWALK1);
+		ob->temp3 = 1;
+	}
+	else if (ob->state == &s_keenwalk3 && ob->temp3 == 0)
+	{
+		SD_PlaySound(SND_WORLDWALK2);
+		ob->temp3 = 1;
+	}
+	else if (ob->state == &s_keenwalk2 ||ob->state == &s_keenwalk4)
+	{
+		ob->temp3 = 0;
+	}
+}
+
+//===========================================================================
+
+/*
+=======================
+=
+= T_LineUp
+=
+= Lines up Keen's position for interacting with tiles (temp1 is desired x)
+=
+=======================
+*/
+
+void T_LineUp(objtype *ob)
+{
+	Sint16 xmove;
+
+	xmove = ob->temp1 - ob->x;
+	if (xmove < 0)
+	{
+		xtry = xtry - tics * 16;
+		if (xtry > xmove)
+			return;
+	}
+	else if (xmove > 0)
+	{
+		xtry = xtry + tics * 16;
+		if (xtry < xmove)
+			return;
+	}
+	xtry = xmove;
+	ob->temp1 = 0;
+	if (!CheckEnterHouse(ob))
+		ob->state = &s_keenstand;
+}
+
+//===========================================================================
+
+/*
+=======================
+=
+= KeenEnterThink
+=
+=======================
+*/
+
+void KeenEnterThink(objtype *ob)
+{
+	Uint16 info;
+	Uint16 far *map;
+
+	map = mapsegs[2] + mapbwidthtable[ob->tilebottom]/2 + ob->tileleft;
+	info = *map;
+#ifdef KEEN5
+	if (!info)
+	{
+		playstate = ex_portout;
+		ob->state = &s_keenenter6;
+		return;
+	}
+	else if (info == 0xB1B1)
+	{
+		playstate = ex_completed;
+		ob->state = &s_keenenter6;
+		return;
+	}
+#endif
+	ob->y = (CONVERT_TILE_TO_GLOBAL(info & 0xFF) - TILEGLOBAL) + 15;
+	ob->x = CONVERT_TILE_TO_GLOBAL(info >> 8);
+	ob->priority = 1;
+	ob->needtoclip = cl_noclip;
+	ChangeState(ob, ob->state->nextstate);
+	ob->needtoclip = cl_midclip;
+	CenterActor(ob);
+}
+
+//===========================================================================
+
+/*
+=======================
+=
+= KeenSwitchThink
+=
+=======================
+*/
+
+void KeenSwitchThink(objtype *ob)
+{
+	Uint16 intile, maptile, newtile, info, sx, sy, tileoff;
+	Uint16 far *map;
+	Uint16 tile, x, y;
+	Sint8 manim;
+
+	tileoff = mapbwidthtable[ob->tiletop]/2 + ob->tilemidx;
+	maptile = mapsegs[1][tileoff];
+	newtile = maptile + (Sint8)tinf[MANIM + maptile];
+	info = mapsegs[2][tileoff];
+	sx = info >> 8;
+	sy = info & 0xFF;
+	intile = tinf[INTILE + maptile];
+
+	RF_MemToMap(&newtile, 1, ob->tilemidx, ob->tiletop, 1, 1);
+	SD_PlaySound(SND_USESWITCH);
+	if (intile == INTILE_BRIDGESWITCH)
+	{
+		//toggle bridge:
+		for (y = sy; sy+2 > y; y++)
+		{
+			map = mapsegs[1] + mapbwidthtable[y]/2 + sx - (y != sy);
+			for (x = sx - (y != sy); x < mapwidth; x++)
+			{
+				tile = *(map++);
+				manim = tinf[MANIM + tile];
+				if (!manim)
+					break;
+
+				tile += manim;
+				RF_MemToMap(&tile, 1, x, y, 1, 1);
+			}
+		}
+	}
+	else
+	{
+		//toggle platform blocker:
+		map = mapsegs[2] + mapbwidthtable[sy]/2 + sx;
+		tile = *map;
+#ifdef KEEN5
+		if (tile >= DIRARROWSTART && tile < DIRARROWEND)
+		{
+			*map = arrowflip[tile-DIRARROWSTART]+DIRARROWSTART;
+			return;
+		}
+#endif
+		*map = tile ^ PLATFORMBLOCK;
+	}
+}
+
+//===========================================================================
+
+/*
+=======================
+=
+= KeenKeyThink
+=
+=======================
+*/
+
+void KeenKeyThink(objtype *ob)
+{
+	Uint16 newtile, info, x, y, tileoff;
+	Uint16 far *map;
+	Uint16 tile, h;
+
+	tileoff = mapbwidthtable[ob->tilebottom]/2 + ob->tilemidx;
+	newtile = mapsegs[1][tileoff] + 18;
+	info = mapsegs[2][tileoff];
+	x = info >> 8;
+	y = info & 0xFF;
+	RF_MemToMap(&newtile, 1, ob->tilemidx, ob->tilebottom, 1, 1);
+	SD_PlaySound(SND_OPENDOOR);
+	GetNewObj(false);
+	new->x = x;
+	new->y = y;
+
+	if (x > mapwidth || x < 2 || y > mapheight || y < 2)
+		Quit("Keyholder points to a bad spot!");
+
+	map = mapsegs[1] + mapbwidthtable[y]/2 + x;
+	tile = *map;
+	h = 1;
+	map += mapwidth;
+	while (*map == tile)
+	{
+			h++;
+			map += mapwidth;
+	}
+	new->temp1 = h;
+	new->active = ac_allways;
+	new->needtoclip = cl_noclip;
+	new->obclass = inertobj;
+	NewState(new, &s_door1);
+}
+
+//===========================================================================
+
+/*
+=======================
+=
+= KeenAirThink
+=
+=======================
+*/
+
+void KeenAirThink(objtype *ob)
+{
+	if (jumpcheat && jumpbutton)
+	{
+		ob->yspeed = -40;
+		jumptime = 18;
+		jumpheld = true;
+	}
+	if (jumptime)
+	{
+		if (jumptime <= tics)
+		{
+			ytry = ob->yspeed * jumptime;
+			jumptime = 0;
+		}
+		else
+		{
+			ytry = ob->yspeed * tics;
+			if (!jumpcheat)
+				jumptime = jumptime - tics;
+		}
+		if (!jumpbutton)
+			jumptime = 0;
+
+		if (jumptime == 0 && ob->state->nextstate)
+			ob->state = ob->state->nextstate;	// switch to second jump stage
+	}
+	else
+	{
+		if (gamestate.difficulty == gd_Easy)
+		{
+			DoWeakGravity(ob);
+		}
+		else
+		{
+			DoGravity(ob);
+		}
+		if (ob->yspeed > 0 && ob->state != &s_keenjump3 && ob->state != &s_keenjump4)
+		{
+			ob->state = ob->state->nextstate;	// switch to third jump stage
+		}
+	}
+
+//-------------
+
+	if (c.xaxis)
+	{
+		ob->xdir = c.xaxis;
+		AccelerateX(ob, c.xaxis*2, 24);
+	}
+	else
+	{
+		FrictionX(ob);
+	}
+
+	if (ob->hitsouth == 17)		// going through a pole hole
+	{
+		ob->xspeed = xtry = 0;
+	}
+
+	if (firebutton && !fireheld)
+	{
+		fireheld = true;
+	//
+	// shoot
+	//
+		switch (c.yaxis)
+		{
+		case -1:
+			ob->state = &s_keenairshootup1;
+			return;
+		case 0:
+			ob->state = &s_keenairshoot1;
+			return;
+		case 1:
+			ob->state = &s_keenairshootdown1;
+			return;
+		}
+	}
+
+	if (pogobutton && !pogoheld)
+	{
+		pogoheld = true;
+		ob->state = &s_keenpogo;
+		jumptime = 0;
+		return;
+	}
+
+	if (c.yaxis == -1)
+		CheckGrabPole(ob);
+}
+
+//===========================================================================
+
+/*
+=======================
+=
+= KeenBounceThink
+=
+= Gives an extra bit of height on the first pogo bounce and creates
+= the "impossible pogo trick" when the jump key is held down
+=
+=======================
+*/
+
+void KeenBounceThink(objtype *ob)
+{
+	ob->yspeed = -48;
+	ytry = ob->yspeed * 6;
+	jumptime = 24;
+	SD_PlaySound(SND_POGOBOUNCE);
+}
+
+//===========================================================================
+
+/*
+=======================
+=
+= KeenPogoThink
+=
+=======================
+*/
+
+void KeenPogoThink(objtype *ob)
+{
+	if (jumptime)
+	{
+		if (jumpbutton || jumptime <= 9)
+		{
+			DoTinyGravity(ob);
+		}
+		else
+		{
+			DoGravity(ob);
+		}
+		if (jumptime <= tics)
+		{
+			jumptime = 0;
+		}
+		else
+		{
+			jumptime = jumptime - tics;
+		}
+		if (jumptime == 0 && ob->state->nextstate)
+			ob->state = ob->state->nextstate;
+	}
+	else
+	{
+		if (gamestate.difficulty == gd_Easy)
+		{
+			DoWeakGravity(ob);
+		}
+		else
+		{
+			DoGravity(ob);
+		}
+	}
+
+	if (c.xaxis)
+	{
+		if (ob->xspeed == 0)
+			ob->xdir = c.xaxis;
+		AccelerateX(ob, c.xaxis, 24);
+	}
+	else
+	{
+		xtry = xtry + ob->xspeed * tics;
+		if (ob->xspeed > 0)
+		{
+			ob->xdir = 1;
+		}
+		else if (ob->xspeed < 0)
+		{
+			ob->xdir = -1;
+		}
+	}
+
+	if (ob->hitsouth == 17)		// going through a pole hole
+	{
+		ob->xspeed = xtry = 0;
+	}
+
+	if (firebutton && !fireheld)
+	{
+		fireheld = true;
+		switch (c.yaxis)
+		{
+		case -1:
+			ob->state = &s_keenairshootup1;
+			return;
+		case 0:
+			ob->state = &s_keenairshoot1;
+			return;
+		case 1:
+			ob->state = &s_keenairshootdown1;
+			return;
+		}
+	}
+
+	if (pogobutton && !pogoheld)
+	{
+		pogoheld = true;
+		ob->state = &s_keenjump3;
+	}
+}
+
+//===========================================================================
+
+/*
+=======================
+=
+= PoleActions
+=
+=======================
+*/
+
+void PoleActions(objtype *ob)
+{
+	if (c.xaxis)
+		ob->xdir = c.xaxis;
+
+	if (firebutton && !fireheld)
+	{
+		fireheld = true;
+		switch (c.yaxis)
+		{
+		case -1:
+			ob->state = &s_keenpoleshootup1;
+			break;
+		case 0:
+			ob->state = &s_keenpoleshoot1;
+			break;
+		case 1:
+			ob->state = &s_keenpoleshootdown1;
+			break;
+		}
+	}
+
+	if (jumpbutton && !jumpheld)		// jump off the pole
+	{
+		jumpheld = true;
+		SD_PlaySound(SND_JUMP);
+		ob->xspeed = polexspeed[c.xaxis+1];
+		ob->yspeed = -20;
+		ob->needtoclip = cl_midclip;
+		jumptime = 10;
+		ob->state = &s_keenjump1;
+		ob->ydir = 1;
+		leavepoletime = lasttimecount;
+	}
+}
+
+/*
+=======================
+=
+= KeenPoleThink
+=
+=======================
+*/
+
+void KeenPoleThink(objtype *ob)
+{
+	Uint16 tile;
+	Uint16 far *map;
+
+	switch (c.yaxis)
+	{
+	case -1:
+		ob->state = &s_keenclimb1;
+		ob->ydir = -1;
+		return;
+	case 1:
+		ob->state = &s_keenslide1;
+		ob->ydir = 1;
+		KeenDropThink(ob);
+		return;
+	}
+
+	if (c.xaxis)
+	{
+	//
+	// walk off pole if right next to ground
+	//
+		map = mapsegs[1] + (mapbwidthtable[ob->tilebottom+1]/2 + ob->tilemidx);
+		tile = *map;
+		if (tinf[NORTHWALL+tile])
+		{
+			ob->xspeed = 0;
+			ob->yspeed = 0;
+			ob->needtoclip = cl_midclip;
+			jumptime = 0;
+			ob->state = &s_keenjump3;
+			ob->ydir = 1;
+			SD_PlaySound(SND_PLUMMET);
+			return;
+		}
+	}
+	PoleActions(ob);
+}
+
+/*
+=======================
+=
+= KeenClimbThink
+=
+=======================
+*/
+
+void KeenClimbThink(objtype *ob)
+{
+	Uint16 far *map;
+
+	map = mapsegs[1] + mapbwidthtable[ob->tiletop]/2 + ob->tilemidx;
+	
+	if ((tinf[INTILE+*map] & 0x7F) != INTILE_POLE)
+	{
+		ytry = 0;
+		ob->state = &s_keenpole;		// ran out of pole
+		PoleActions(ob);
+		return;
+	}
+
+	switch (c.yaxis)
+	{
+	case 0:
+		ob->state = &s_keenpole;
+		ob->ydir = 0;
+		break;
+
+	case 1:
+		ob->state = &s_keenslide1;
+		ob->ydir = 1;
+		KeenDropThink(ob);
+		break;
+	}
+
+	PoleActions(ob);
+}
+
+/*
+=======================
+=
+= KeenDropThink
+=
+=======================
+*/
+
+void KeenDropThink(objtype *ob)
+{
+	Uint16 far *map;
+	Uint16 y;
+
+	y = CONVERT_GLOBAL_TO_TILE(ob->bottom - 4*PIXGLOBAL);
+	map = mapsegs[1] + mapbwidthtable[y]/2 + ob->tilemidx;
+
+	if ((tinf[INTILE+*map] & 0x7F) != INTILE_POLE)
+	{
+		SD_PlaySound(SND_PLUMMET);
+		ob->state = &s_keenjump3;		// ran out of pole
+		jumptime = 0;
+		ob->xspeed = polexspeed[c.xaxis+1];
+		ob->yspeed = 0;
+		ob->needtoclip = cl_midclip;
+		ob->tilebottom--;
+		return;
+	}
+
+	switch (c.yaxis)
+	{
+	case -1:
+		ob->state = &s_keenclimb1;
+		ob->ydir = -1;
+		break;
+
+	case 0:
+		ob->state = &s_keenpole;
+		ob->ydir = 0;
+		break;
+	}
+
+	PoleActions(ob);
+}
+
+//===========================================================================
+
+/*
+=======================
+=
+= KeenDropDownThink
+=
+=======================
+*/
+
+void KeenDropDownThink(objtype *ob)
+{
+	ob->needtoclip = cl_midclip;
+}
+
+//===========================================================================
+
+/*
+=======================
+=
+= KeenHoldThink
+=
+=======================
+*/
+
+void KeenHoldThink(objtype *ob)
+{
+	Uint16 tile;
+
+	if (c.yaxis == -1 || ob->xdir == c.xaxis)
+	{
+		ob->state = &s_keenclimbup;
+		if (ob->xdir == 1)
+		{
+			tile = *(mapsegs[1]+mapbwidthtable[ob->tiletop-1]/2+ob->tileright);
+		}
+		else
+		{
+			tile = *(mapsegs[1]+mapbwidthtable[ob->tiletop-1]/2+ob->tileleft);
+		}
+		if (ob->xdir == 1)
+		{
+			ytry = -16*PIXGLOBAL;
+		}
+		else
+		{
+			ytry = -8*PIXGLOBAL;
+		}
+		if (!(tinf[INTILE+tile] & INTILE_FOREGROUND))
+			ob->priority = 3;
+	}
+	else if (c.yaxis == 1 || c.xaxis && ob->xdir != c.xaxis)
+	{
+		ob->state = &s_keenjump3;
+		ob->needtoclip = cl_midclip;
+	}
+}
+
+//===========================================================================
+
+/*
+=======================
+=
+= KeenShootThink
+=
+=======================
+*/
+
+void KeenShootThink(objtype *ob)
+{
+// can't use &<var> in a switch statement...
+
+	if (ob->state == &s_keenshoot1)
+	{
+		if (ob->xdir == 1)
+		{
+			SpawnShot(ob->x + 16*PIXGLOBAL, ob->y + 4*PIXGLOBAL, dir_East);
+		}
+		else
+		{
+			SpawnShot(ob->x - 8*PIXGLOBAL, ob->y + 4*PIXGLOBAL, dir_West);
+		}
+	}
+	if (ob->state == &s_keenairshoot2)
+	{
+		if (ob->xdir == 1)
+		{
+			SpawnShot(ob->x + 16*PIXGLOBAL, ob->y + 2*PIXGLOBAL, dir_East);
+		}
+		else
+		{
+			SpawnShot(ob->x, ob->y + 2*PIXGLOBAL, dir_West);
+		}
+	}
+	if (ob->state == &s_keenairshootdown2)
+	{
+		SpawnShot(ob->x + 8*PIXGLOBAL, ob->y + 18*PIXGLOBAL, dir_South);
+	}
+	if (ob->state == &s_keenairshootup2)
+	{
+		SpawnShot(ob->x + 5*PIXGLOBAL, ob->y - 10*PIXGLOBAL, dir_North);
+	}
+	if (ob->state == &s_keenshootup1)
+	{
+		SpawnShot(ob->x + 5*PIXGLOBAL, ob->y - 10*PIXGLOBAL, dir_North);
+	}
+	if (ob->state == &s_keenpoleshoot1)
+	{
+		if (ob->xdir == 1)
+		{
+			SpawnShot(ob->x + 16*PIXGLOBAL, ob->y + 4*PIXGLOBAL, dir_East);
+		}
+		else
+		{
+			SpawnShot(ob->x - 8*PIXGLOBAL, ob->y + 4*PIXGLOBAL, dir_West);
+		}
+	}
+	if (ob->state == &s_keenpoleshootup1)
+	{
+		if (ob->xdir == 1)
+		{
+			SpawnShot(ob->x + 6*PIXGLOBAL, ob->y + 4*PIXGLOBAL, dir_North);
+		}
+		else
+		{
+			SpawnShot(ob->x + 12*PIXGLOBAL, ob->y + 4*PIXGLOBAL, dir_North);
+		}
+	}
+	if (ob->state == &s_keenpoleshootdown1)
+	{
+		if (ob->xdir == 1)
+		{
+			SpawnShot(ob->x + 6*PIXGLOBAL, ob->y + 24*PIXGLOBAL, dir_South);
+		}
+		else
+		{
+			SpawnShot(ob->x + 12*PIXGLOBAL, ob->y + 24*PIXGLOBAL, dir_South);
+		}
+	}
+}
+
+//===========================================================================
+
+/*
+=======================
+=
+= T_PullUp1
+=
+=======================
+*/
+
+void T_PullUp1(objtype *ob)
+{
+	if (ob->xdir == 1)
+	{
+		xtry = 8*PIXGLOBAL;
+	}
+	else
+	{
+		ytry = -8*PIXGLOBAL;
+	}
+}
+
+/*
+=======================
+=
+= T_PullUp2
+=
+=======================
+*/
+
+void T_PullUp2(objtype *ob)
+{
+	if (ob->xdir == 1)
+	{
+		xtry = 8*PIXGLOBAL;
+		ytry = -8*PIXGLOBAL;
+	}
+	else
+	{
+		xtry = -8*PIXGLOBAL;
+		ytry = -8*PIXGLOBAL;
+	}
+}
+
+/*
+=======================
+=
+= T_PullUp3
+=
+=======================
+*/
+
+#pragma argsused
+void T_PullUp3(objtype *ob)
+{
+	ytry = -8*PIXGLOBAL;
+}
+
+/*
+=======================
+=
+= T_PulledUp
+=
+=======================
+*/
+
+void T_PulledUp(objtype *ob)
+{
+	ob->needtoclip = cl_midclip;
+	ob->priority = 1;
+	ytry = 8*PIXGLOBAL;
+}
+
+//===========================================================================
+
+/*
+=======================
+=
+= KeenDieThink
+=
+=======================
+*/
+
+void KeenDieThink(objtype *ob)
+{
+	DoWeakGravity(ob);
+	xtry = ob->xspeed * tics;
+	if (!OnScreen(ob))
+		playstate = ex_died;
+}
+
+/*
+=============================================================================
+
+						CONTACT ROUTINES
+
+=============================================================================
+*/
+
+/*
+============================
+=
+= KillKeen
+=
+============================
+*/
+
+void KillKeen(void)
+{
+	if (invincible || godmode)
+		return;
+
+	if (player->state != &s_keendead)
+	{
+
+		moonok = 0;
+		invincible = 30;	//0.43 seconds
+		keenkilled = true;
+		player->needtoclip = cl_noclip;
+		player->priority = 3;
+#ifdef KEEN4
+		if (mapon == 17)
+		{
+			if (US_RndT() < 0x80)
+			{
+				ChangeState(player, &s_keensuitdie1);
+			}
+			else
+			{
+				ChangeState(player, &s_keensuitdie2);
+			}
+		}
+		else
+#endif
+		{
+			if (US_RndT() < 0x80)
+			{
+				ChangeState(player, &s_keendie1);
+			}
+			else
+			{
+				ChangeState(player, &s_keendie2);
+			}
+		}
+		SD_PlaySound(SND_KEENDEAD);
+		player->yspeed = -40;
+		player->xspeed = 16;
+	}
+}
+
+/*
+============================
+=
+= KeenContact
+=
+============================
+*/
+
+void KeenContact(objtype *ob, objtype *hit)
+{
+	switch (hit->obclass)
+	{
+	case bonusobj:
+		switch (hit->temp1)
+		{
+		case 0:
+		case 1:
+		case 2:
+		case 3:
+		case 4:
+		case 5:
+		case 6:
+		case 7:
+		case 8:
+		case 9:
+		case 10:
+		case 11:
+#ifdef KEEN5
+		case 12:
+#endif
+			SD_PlaySound(bonussound[hit->temp1]);
+			hit->obclass = inertobj;
+			hit->priority = 3;
+			hit->shapenum = bonussprite[hit->temp1];
+			GivePoints(bonuspoints[hit->temp1]);
+			if (hit->temp1 < 4)
+			{
+				gamestate.keys[hit->temp1]++;
+			}
+			else if (hit->temp1 == 10)
+			{
+				gamestate.lives++;
+			}
+			else if (hit->temp1 == 11)
+			{
+				gamestate.ammo += shotsinclip[gamestate.difficulty];
+			}
+#ifdef KEEN5
+			else if (hit->temp1 == 12)
+			{
+				gamestate.keycard = true;
+			}
+#endif
+			ChangeState(hit, &s_bonusrise);
+		}
+		break;
+
+#if defined KEEN4
+	case oracleobj:
+		if (!ob->hitnorth)
+			break;
+
+		if (mapon == 14)
+		{
+			RescueJanitor();
+			RF_ForceRefresh();
+			RemoveObj(hit);
+		}
+		else
+		{
+			SD_PlaySound(SND_LINDSEY);
+			playstate = ex_rescued;
+		}
+		break;
+	case stunnedobj:
+		if (hit->temp4 != bounderobj)
+			break;
+		//no break here -- drop through to platformobj is intended!
+	case platformobj:
+		if (!gamestate.riding)
+		{
+			ClipToSpriteTop(ob, hit);
+		}
+		else
+			return;
+		break;
+	case bounderobj:
+		ClipToSprite(ob, hit, false);
+		break;
+	case lindseyobj:
+		PrincessLindsey();
+		RemoveObj(hit);
+		RF_ForceRefresh();
+		break;
+	case footobj:
+		playstate = ex_foot;
+		break;
+#elif defined KEEN5
+	case platformobj:
+		if (!gamestate.riding)
+			ClipToSpriteTop(ob, hit);
+		break;
+#elif defined KEEN6
+	case stunshotobj:
+		if (hit->temp4)
+		{
+			ExplodeShot(hit);
+			ChangeState(ob, &s_keenstun);
+		}
+		// BUG: there is no break here - this causes the impossible bullet bug
+	case platformobj:
+		if (!gamestate.riding)
+			ClipToSpriteTop(ob, hit);
+		break;
+#endif
+	}
+}
+
+/*
+============================
+=
+= KeenPosContact
+=
+============================
+*/
+
+void KeenPosContact(objtype *ob, objtype *hit)
+{
+	switch (hit->obclass)
+	{
+#if defined KEEN4
+	case platformobj:
+		// BUG: priority is not reset here
+		ob->needtoclip = cl_midclip;
+		ChangeState(ob, &s_keenjump3);
+		jumptime = ob->xspeed = ob->yspeed = 0;
+		ClipToSpriteTop(ob, hit);
+		break;
+	case madmushroomobj:
+	case arachnutobj:
+	case berkeloidobj:
+		KillKeen();
+		break;
+	case bounderobj:
+		ob->priority = 1;
+		ob->needtoclip = cl_midclip;
+		ChangeState(ob, &s_keenjump3);
+		jumptime = ob->xspeed = ob->yspeed = 0;
+		ClipToSprite(ob, hit, false);
+		break;
+#elif defined KEEN5
+	case platformobj:
+		// BUG: priority is not reset here
+		ob->needtoclip = cl_midclip;
+		ChangeState(ob, &s_keenjump3);
+		jumptime = ob->xspeed = ob->yspeed = 0;
+		ClipToSpriteTop(ob, hit);
+		break;
+	case amptonobj:
+	case scottieobj:
+		ob->priority = 1;
+		ob->needtoclip = cl_midclip;
+		ChangeState(ob, &s_keenjump3);
+		jumptime = ob->xspeed = ob->yspeed = 0;
+		break;
+#elif defined KEEN6
+	case platformobj:
+	case gikobj:
+	case flectobj:
+	case bloogletobj:
+		ob->priority = 1;
+		ob->needtoclip = cl_midclip;
+		ChangeState(ob, &s_keenjump3);
+		jumptime = ob->xspeed = ob->yspeed = 0;
+		ClipToSpriteTop(ob, hit);	// BUG: allows Keen to stand on Blooglets and Flects
+		break;
+#endif
+	}
+}
+
+/*
+============================
+=
+= HandleRiding
+=
+============================
+*/
+
+void HandleRiding(objtype *ob)
+{
+	objtype *plat;
+
+	plat = gamestate.riding;
+	if (ob->right < plat->left || ob->left > plat->right)
+	{
+		gamestate.riding = NULL;
+	}
+	else if (ob->ymove < 0)
+	{
+		gamestate.riding = NULL;
+		if (plat->ymove < 0)
+		{
+			xtry = 0;
+			ytry = plat->ymove;
+			PushObj(ob);
+		}
+	}
+	else
+	{
+		xtry = plat->xmove;
+		ytry = plat->top - ob->bottom - 16;
+		PushObj(ob);
+
+#if GRMODE == CGAGR
+		if (ob->xmove == plat->xmove)
+		{
+			ob->x &= ~0x3F;
+			ob->x |= plat->x & 0x3F;
+		}
+#else
+		if (nopan)
+		{
+			ob->x &= ~0x7F;
+			ob->x |= plat->x & 0x7F;
+		}
+		else
+		{
+			ob->x |= plat->x & 0x1F;
+		}
+#endif
+
+		if (ob->hitsouth)
+		{
+			gamestate.riding = NULL;
+		}
+		else
+		{
+			ob->hitnorth = 25;
+		}
+	}
+}
+
+/*
+============================
+=
+= TileBonus
+=
+============================
+*/
+
+void TileBonus(Uint16 x, Uint16 y, Uint16 bonus)
+{
+	RF_MemToMap(&zeromap, 1, x, y, 1, 1);
+	SD_PlaySound(bonussound[bonus]);
+	GivePoints(bonuspoints[bonus]);
+	if (bonus < 4)
+	{
+		gamestate.keys[bonus]++;
+	}
+	else if (bonus == 10)
+	{
+		gamestate.lives++;
+	}
+	else if (bonus == 11)
+	{
+		gamestate.ammo += shotsinclip[gamestate.difficulty];
+	}
+	GetNewObj(true);
+	new->obclass = inertobj;
+	new->priority = 3;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y);
+	new->ydir = -1;
+	new->temp2 = new->shapenum = bonussprite[bonus];
+	NewState(new, &s_bonusrise);
+	new->needtoclip = cl_noclip;
+}
+
+/*
+============================
+=
+= GiveDrop
+=
+============================
+*/
+
+void GiveDrop(Uint16 x, Uint16 y)
+{
+	RF_MemToMap(&zeromap, 1, x, y, 1, 1);
+	SD_PlaySound(SND_GETWATER);
+	SpawnSplash(x, y);
+	if (++gamestate.drops == 100)
+	{
+		gamestate.drops = 0;
+		SD_PlaySound(SND_EXTRAKEEN);
+		gamestate.lives++;
+		GetNewObj(true);
+		new->obclass = inertobj;
+		new->priority = 3;
+		new->x = CONVERT_TILE_TO_GLOBAL(x);
+		new->y = CONVERT_TILE_TO_GLOBAL(y-1);
+		new->ydir = -1;
+		new->temp2 = new->shapenum = BONUS100UPSPR;
+		NewState(new, &s_bonusrise);
+		new->needtoclip = cl_noclip;
+	}
+}
+
+/*
+============================
+=
+= CheckInTiles
+=
+============================
+*/
+
+void CheckInTiles(objtype *ob)
+{
+	Uint16 x, y;
+	Uint16 far *map;
+	Uint16 rowdelta, intile, midx;
+
+	if (moonok == 1)
+		moonok = 0;
+
+	map = mapsegs[1] + mapbwidthtable[ob->tiletop]/2 + ob->tileleft;
+	rowdelta = mapwidth - (ob->tileright - ob->tileleft + 1);
+	for (y = ob->tiletop; y <= ob->tilebottom; y++, map += rowdelta)
+	{
+		for (x = ob->tileleft; x <= ob->tileright; x++, map++)
+		{
+			if ((intile = tinf[INTILE + *map] & INTILE_TYPEMASK) != 0)
+			{
+				switch (intile)
+				{
+				case INTILE_DEADLY:
+					KillKeen();
+					break;
+
+				case INTILE_DROP:
+					GiveDrop(x, y);
+					break;
+
+				case INTILE_GEMSOCKET0:
+				case INTILE_GEMSOCKET1:
+				case INTILE_GEMSOCKET2:
+				case INTILE_GEMSOCKET3:
+					if (ob->tilebottom != y || !ob->hitnorth
+						|| ob->state == &s_keenkey
+						|| !gamestate.keys[intile-INTILE_GEMSOCKET0])
+					{
+						return;
+					}
+
+					midx = CONVERT_TILE_TO_GLOBAL(x) + -4*PIXGLOBAL;
+					if (ob->x != midx)
+					{
+						ob->temp1 = midx;
+						ob->state = &s_keenlineup;
+						return;
+					}
+					else
+					{
+						gamestate.keys[intile-INTILE_GEMSOCKET0]--;
+						ChangeState(ob, &s_keenkey);
+					}
+					break;
+
+				case INTILE_MOON:
+					if (moonok == 0)
+						moonok = 1;
+					break;
+
+				case INTILE_BONUS100:
+				case INTILE_BONUS200:
+				case INTILE_BONUS500:
+				case INTILE_BONUS1000:
+				case INTILE_BONUS2000:
+				case INTILE_BONUS5000:
+				case INTILE_EXTRALIFE:
+				case INTILE_AMMO:
+					TileBonus(x, y, (intile-INTILE_BONUS100)+4);
+					break;
+				}
+			}
+		}
+	}
+}
+
+/*
+=============================================================================
+
+						 REACTION ROUTINES
+
+=============================================================================
+*/
+
+
+/*
+============================
+=
+= KeenSimpleReact
+=
+============================
+*/
+
+void KeenSimpleReact(objtype *ob)
+{
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+
+/*
+============================
+=
+= KeenStandReact
+=
+============================
+*/
+
+void KeenStandReact(objtype *ob)
+{
+	if (!ob->hitnorth)
+	{
+	//
+	// walked off an edge
+	//
+		SD_PlaySound(SND_PLUMMET);
+		ob->xspeed = ob->xdir * 8;
+		ob->yspeed = 0;
+		ChangeState(ob, &s_keenjump3);
+		jumptime = 0;
+	}
+	else if ((ob->hitnorth & ~7) == 8)	// deadly floor!
+	{
+		KillKeen();
+	}
+	else if (ob->hitnorth == 41)
+	{
+		xtry = tics * 8;
+		ytry = 0;
+		ob->temp1 = 0;
+		ClipToWalls(ob);
+	}
+	else if (ob->hitnorth == 49)
+	{
+		xtry = tics * -8;
+		ytry = 0;
+		ob->temp1 = 0;
+		ClipToWalls(ob);
+	}
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+============================
+=
+= KeenWalkReact
+=
+============================
+*/
+
+void KeenWalkReact(objtype *ob)
+{
+	if (!ob->hitnorth)
+	{
+	//
+	// walked off an edge
+	//
+		SD_PlaySound(SND_PLUMMET);
+		ob->xspeed = ob->xdir * 8;
+		ob->yspeed = 0;
+		ChangeState(ob, &s_keenjump3);
+		jumptime = 0;
+	}
+	else if ((ob->hitnorth & ~7) == 8)	// deadly floor!
+	{
+		KillKeen();
+	}
+	else if (ob->hitnorth == 41)
+	{
+		xtry = tics * 8;
+		ytry = 0;
+		ClipToWalls(ob);
+	}
+	else if (ob->hitnorth == 49)
+	{
+		xtry = tics * -8;
+		ytry = 0;
+		ClipToWalls(ob);
+	}
+	else if (ob->hiteast && ob->xdir == -1 || ob->hitwest && ob->xdir == 1)
+	{
+	//
+	// ran into a wall
+	//
+		ob->ticcount = 0;
+		ob->state = &s_keenstand;
+		ob->shapenum = ob->xdir == 1? s_keenstand.rightshapenum : s_keenstand.leftshapenum;
+	}
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+============================
+=
+= KeenAirReact
+=
+============================
+*/
+
+void KeenAirReact(objtype *ob)
+{
+	Uint16 far *map;
+	Uint16 oldtop, graby, ty, tile;
+
+	if (ob->hiteast && ob->xdir == -1 || ob->hitwest && ob->xdir == 1)
+		ob->xspeed = 0;
+
+	if (ob->hitsouth)
+	{
+		if (ob->hitsouth == 17)	// jumping up through a pole hole
+		{
+			ob->y -= 2*PIXGLOBAL;
+			ob->top -= 2*PIXGLOBAL;
+			ob->xspeed = 0;
+			ob->x = CONVERT_TILE_TO_GLOBAL(ob->tilemidx) - 2*PIXGLOBAL;
+		}
+		else
+		{
+#ifdef KEEN6
+			if (ob->hitsouth == 33)
+			{
+				FlipBigSwitch(ob, false);
+			}
+#endif
+			if (!jumpcheat)
+			{
+				SD_PlaySound(SND_HELMETHIT);
+				if (ob->hitsouth > 1)
+				{
+					ob->yspeed += 16;
+					if (ob->yspeed < 0)	// push away from slopes
+						ob->yspeed = 0;
+				}
+				else
+				{
+					ob->yspeed = 0;
+				}
+				jumptime = 0;
+			}
+		}
+	}
+
+	if (ob->hitnorth)
+	{
+		ob->ymove = 0;
+		if ((ob->hitnorth & ~7) == 8)	// deadly floor!
+		{
+			KillKeen();
+		}
+		else
+		{
+#if defined KEEN5
+			if (ob->hitnorth == 57)
+			{
+				SD_PlaySound(SND_LANDONFUSE);
+			}
+#elif defined KEEN6
+			if (ob->hitnorth == 33)
+			{
+				FlipBigSwitch(ob, true);
+			}
+#endif
+			if (ob->hitnorth != 25 || !jumptime)	// KLUDGE to allow jumping off
+			{
+				ob->temp1 = ob->temp2 = 0;
+				if (ob->state == &s_keenairshoot1)
+				{
+					ChangeState(ob, &s_keenshoot1);
+				}
+				else if (ob->state == &s_keenairshootup1)
+				{
+					ChangeState(ob, &s_keenshootup1);
+				}
+				else if (c.xaxis)
+				{
+					ChangeState(ob, &s_keenwalk1);
+				}
+				else
+				{
+					ChangeState(ob, &s_keenstand);
+				}
+				SD_PlaySound(SND_LAND);
+			}
+		}
+	}
+	else if (ob->ymove > 0)
+	{
+//
+// check if there is an edge to grab
+//
+		oldtop = ob->top - ob->ymove;
+		graby = ((ob->top - 4*PIXGLOBAL) & 0xFF00) + 4*PIXGLOBAL;
+		ty = CONVERT_GLOBAL_TO_TILE(graby) - 1;
+		if (oldtop < graby && ob->top >= graby)
+		{
+			if (c.xaxis == -1)
+			{
+				map = mapsegs[1] + mapbwidthtable[ty]/2 + ob->tileleft;
+				if (ob->hiteast)
+					map--;
+				tile = *map;
+				if (!tinf[EASTWALL + tile] && !tinf[WESTWALL + tile]
+					&& !tinf[NORTHWALL + tile] && !tinf[SOUTHWALL + tile]
+					&& tinf[EASTWALL + map[mapwidth]] && tinf[NORTHWALL + map[mapwidth]]
+					)
+				{
+					ob->xdir = -1;
+					ob->needtoclip = cl_noclip;
+					ob->x = (ob->x & 0xFF00) + 8*PIXGLOBAL;
+					ob->y = graby - 4*PIXGLOBAL;
+					ob->yspeed = ob->ymove = 0;
+					ChangeState(ob, &s_keenholdon);
+				}
+			}
+			else if (c.xaxis == 1)
+			{
+				map = mapsegs[1] + mapbwidthtable[ty]/2 + ob->tileright;
+				if (ob->hitwest)
+					map++;
+				tile = *map;
+				if (!tinf[EASTWALL + tile] && !tinf[WESTWALL + tile]
+					&& !tinf[NORTHWALL + tile] && !tinf[SOUTHWALL + tile]
+					&& tinf[WESTWALL + map[mapwidth]] && tinf[NORTHWALL + map[mapwidth]]
+					)
+				{
+					ob->xdir = 1;
+					ob->needtoclip = cl_noclip;
+					ob->x = (ob->x & 0xFF00) + 16*PIXGLOBAL;
+					ob->y = graby - 4*PIXGLOBAL;
+					ob->yspeed = ob->ymove = 0;
+					ChangeState(ob, &s_keenholdon);
+				}
+			}
+		}
+	}
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+#ifdef KEEN5
+/*
+============================
+=
+= BreakFuse
+=
+============================
+*/
+
+void BreakFuse(Uint16 tileX, Uint16 tileY)
+{
+	Uint16 tiles[] = {1932, 1950};	// should be 'static' for less overhead
+
+	// The original disassembly had some code here equivalent to this:
+	//
+	// _AX = tiles[0];
+	// _DX = 4;
+	//
+	// As it turned out, that was just a compiler quirk.
+
+	SpawnFuseFlash(tileX, tileY);
+	if (--gamestate.numfuses == 0)
+	{
+		SpawnDeadMachine();
+	}
+	RF_MemToMap(tiles, 1, tileX, tileY, 1, 2);
+}
+#endif
+
+/*
+============================
+=
+= KeenPogoReact
+=
+============================
+*/
+
+void KeenPogoReact(objtype *ob)
+{
+	if (ob->hiteast && ob->xdir == -1 || ob->hitwest && ob->xdir == 1)
+		ob->xspeed = 0;
+
+	if (ob->hitsouth)
+	{
+		if (ob->hitsouth == 17)	// jumping up through a pole hole
+		{
+			ob->y -= 2*PIXGLOBAL;
+			ob->top -= 2*PIXGLOBAL;
+			ob->xspeed = 0;
+			ob->x = CONVERT_TILE_TO_GLOBAL(ob->tilemidx) - 2*PIXGLOBAL;
+		}
+		else
+		{
+#ifdef KEEN6
+			if (ob->hitsouth == 33)
+			{
+				FlipBigSwitch(ob, false);
+			}
+#endif
+			if (!jumpcheat)
+			{
+				SD_PlaySound(SND_HELMETHIT);
+				if (ob->hitsouth > 1)
+				{
+					ob->yspeed += 16;
+					if (ob->yspeed < 0)	// push away from slopes
+						ob->yspeed = 0;
+				}
+				else
+				{
+					ob->yspeed = 0;
+				}
+				jumptime = 0;
+			}
+		}
+	}
+
+	if (ob->hitnorth)
+	{
+		ob->ymove = 0;
+		if ((ob->hitnorth & ~7) == 8)	// deadly floor!
+		{
+			KillKeen();
+		}
+		else
+		{
+#if defined KEEN5
+			if (ob->hitnorth == 57)
+			{
+				if (ob->yspeed < 48)
+				{
+					SD_PlaySound(SND_LANDONFUSE);
+				}
+				else
+				{
+					BreakFuse(ob->tilemidx, ob->tilebottom);
+					RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+					return;
+				}
+			}
+#elif defined KEEN6
+			if (ob->hitnorth == 33)
+			{
+				FlipBigSwitch(ob, true);
+			}
+			else if (ob->hitnorth == 41)
+			{
+				ob->xspeed += 8;
+				if (ob->xspeed > 8)
+					ob->xspeed = 8;
+			}
+			else if (ob->hitnorth == 49)
+			{
+				ob->xspeed -= 8;
+				if (ob->xspeed < -8)
+					ob->xspeed = -8;
+			}
+#endif
+			if (ob->hitnorth != 25 || !jumptime)	// KLUDGE to allow jumping off
+			{
+				ob->yspeed = -48;
+				jumptime = 24;
+				SD_PlaySound(SND_POGOBOUNCE);
+				ChangeState(ob, &s_keenpogo);
+			}
+		}
+	}
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+============================
+=
+= KeenPoleReact
+=
+============================
+*/
+
+void KeenPoleReact(objtype *ob)
+{
+	Uint16 far *map;
+	Uint16 ymove;
+
+	map = mapsegs[1] + mapbwidthtable[ob->tilebottom]/2 + ob->tilemidx;
+	if (tinf[NORTHWALL + *map] == 1)
+	{
+		ymove = (ob->bottom & 0xFF) + 1;
+		ob->y -= ymove;
+		ob->bottom -= ymove;
+		ob->tilebottom--;
+		ob->needtoclip = cl_midclip;
+		ChangeState(ob, &s_keenlookdown);
+	}
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
diff --git a/16/keen456/KEEN4-6/CK_KEEN2.C b/16/keen456/KEEN4-6/CK_KEEN2.C
new file mode 100755
index 00000000..e30e5d7a
--- /dev/null
+++ b/16/keen456/KEEN4-6/CK_KEEN2.C
@@ -0,0 +1,1606 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+/*
+CK_KEEN2.C
+==========
+
+Contains the following actor types (in this order):
+
+- Score Box & Demo sprites
+- Keen (world map)
+- Flags (world map)
+- Neural Stunner Shots
+- Gem Door Opener
+- Card Door Opener (Keen 5 only)
+
+*/
+
+#include "CK_DEF.H"
+
+Direction opposite[8] = {dir_South, dir_SouthWest, dir_West, dir_NorthWest, dir_North, dir_NorthEast, dir_East, dir_SouthEast};
+
+/*
+=============================================================================
+
+						 SCORE BOX ROUTINES
+
+=============================================================================
+*/
+
+statetype s_score         = {  0,   0, think, false, false, 0, 0, 0, NULL, NULL, NULL, NULL};
+statetype s_demo          = {DEMOPLAQUESPR, DEMOPLAQUESPR, think, false, false, 0, 0, 0, NULL, NULL, NULL, NULL};
+
+/*
+======================
+=
+= SpawnScore
+=
+======================
+*/
+
+void SpawnScore(void)
+{
+	scoreobj->obclass = inertobj;
+	scoreobj->priority = 3;
+	scoreobj->active = ac_allways;
+	scoreobj->needtoclip = cl_noclip;
+	scoreobj->temp2 = -1;
+	scoreobj->temp1 = -1;
+	scoreobj->temp3 = -1;
+	scoreobj->temp4 = -1;
+	if (scorescreenkludge)
+	{
+		scoreobj->state = &sc_deadstate;
+	}
+	else if (!DemoMode)
+	{
+		NewState(scoreobj, &s_score);
+	}
+	else
+	{
+		NewState(scoreobj, &s_demo);
+		CA_MarkGrChunk(DEMOPLAQUESPR);
+	}
+}
+
+
+// Taken from Keen Dreams: MemDrawChar and ShiftScore
+
+/*
+======================
+=
+= MemDrawChar
+=
+======================
+*/
+
+#if GRMODE == EGAGR
+
+void MemDrawChar(Sint16 char8, Uint8 far *dest, Uint16 width, Uint16 planesize)
+{
+	Uint16 source = (Uint16)grsegs[STARTTILE8];	// Note: this differs from Keen Dreams source
+
+asm	mov	si,[char8]
+asm	shl	si,1
+asm	shl	si,1
+asm	shl	si,1
+asm	shl	si,1
+asm	shl	si,1		// index into char 8 segment
+
+asm	mov	ds,[WORD PTR source]	// Note: this differs from Keen Dreams source
+asm	mov	es,[WORD PTR dest+2]
+
+asm	mov	cx,4		// draw four planes
+asm	mov	bx,[width]
+asm	dec	bx
+
+planeloop:
+
+asm	mov	di,[WORD PTR dest]
+
+asm	movsb
+asm	add	di,bx
+asm	movsb
+asm	add	di,bx
+asm	movsb
+asm	add	di,bx
+asm	movsb
+asm	add	di,bx
+asm	movsb
+asm	add	di,bx
+asm	movsb
+asm	add	di,bx
+asm	movsb
+asm	add	di,bx
+asm	movsb
+
+asm	mov	ax,[planesize]
+asm	add	[WORD PTR dest],ax
+
+asm	loop	planeloop
+
+asm	mov	ax,ss
+asm	mov	ds,ax
+}
+
+#elif GRMODE == CGAGR
+
+void MemDrawChar (int char8,byte far *dest,unsigned width,unsigned planesize)
+{
+asm	mov	si,[char8]
+asm	shl	si,1
+asm	shl	si,1
+asm	shl	si,1
+asm	shl	si,1		// index into char 8 segment
+
+asm	mov	ds,[WORD PTR grsegs+STARTTILE8*2]
+asm	mov	es,[WORD PTR dest+2]
+
+asm	mov	bx,[width]
+asm	sub	bx,2
+
+asm	mov	di,[WORD PTR dest]
+
+asm	movsw
+asm	add	di,bx
+asm	movsw
+asm	add	di,bx
+asm	movsw
+asm	add	di,bx
+asm	movsw
+asm	add	di,bx
+asm	movsw
+asm	add	di,bx
+asm	movsw
+asm	add	di,bx
+asm	movsw
+asm	add	di,bx
+asm	movsw
+
+asm	mov	ax,ss
+asm	mov	ds,ax
+
+	planesize++;		// shut the compiler up
+}
+#endif
+
+/*
+====================
+=
+= ShiftScore
+=
+====================
+*/
+#if GRMODE == EGAGR
+void ShiftScore (void)
+{
+	spritetabletype far *spr;
+	spritetype _seg *dest;
+
+	spr = &spritetable[SCOREBOXSPR-STARTSPRITES];
+	dest = (spritetype _seg *)grsegs[SCOREBOXSPR];
+
+	CAL_ShiftSprite (FP_SEG(dest),dest->sourceoffset[0],
+		dest->sourceoffset[1],spr->width,spr->height,2);
+
+	CAL_ShiftSprite (FP_SEG(dest),dest->sourceoffset[0],
+		dest->sourceoffset[2],spr->width,spr->height,4);
+
+	CAL_ShiftSprite (FP_SEG(dest),dest->sourceoffset[0],
+		dest->sourceoffset[3],spr->width,spr->height,6);
+}
+#endif
+
+/*
+===============
+=
+= UpdateScore
+=
+===============
+*/
+
+void UpdateScore(objtype *ob)
+{
+	char		str[10],*ch;
+	spritetype	_seg	*block;
+	Uint8		far *dest;
+	Uint16	i, length, width, planesize, number;
+	boolean changed;
+
+	if (scorescreenkludge)
+		return;
+
+	if (DemoMode)
+	{
+		DrawDemoPlaque(ob);
+		return;
+	}
+
+	if (!showscorebox)
+		return;
+
+	changed = false;
+
+//code below is a combination of ScoreThink and ScoreReact from Keen Dreams with minor changes
+
+//
+// score changed
+//
+	if ((gamestate.score>>16) != ob->temp1
+		|| (Uint16)gamestate.score != ob->temp2 )
+	{
+		block = (spritetype _seg *)grsegs[SCOREBOXSPR];
+		width = block->width[0];
+		planesize = block->planesize[0];
+		dest = (Uint8 far *)grsegs[SCOREBOXSPR]+block->sourceoffset[0]
+			+ planesize + width*4;
+
+		ltoa (gamestate.score,str,10);
+
+		// erase leading spaces
+		length = strlen(str);
+		for (i=9;i>length;i--)
+			MemDrawChar (41,dest+=CHARWIDTH,width,planesize);
+
+		// draw digits
+		ch = str;
+		while (*ch)
+			MemDrawChar (*ch++ - '0'+42,dest+=CHARWIDTH,width,planesize);
+
+#if GRMODE == EGAGR
+		ShiftScore ();
+#endif
+		ob->needtoreact = true;
+		ob->temp1 = gamestate.score>>16;
+		ob->temp2 = gamestate.score;
+
+		changed = true;
+	}
+
+//
+// ammo changed
+//
+	number = gamestate.ammo;
+	if (number != ob->temp3)
+	{
+		block = (spritetype _seg *)grsegs[SCOREBOXSPR];
+		width = block->width[0];
+		planesize = block->planesize[0];
+		dest = (byte far *)grsegs[SCOREBOXSPR]+block->sourceoffset[0]
+			+ planesize + width*20 + 7*CHARWIDTH;
+
+		if (number > 99)
+			strcpy (str,"99");
+		else
+			ltoa (number,str,10);
+
+		// erase leading spaces
+		length = strlen(str);
+		for (i=2;i>length;i--)
+			MemDrawChar (41,dest+=CHARWIDTH,width,planesize);
+
+		// draw digits
+		ch = str;
+		while (*ch)
+			MemDrawChar (*ch++ - '0'+42,dest+=CHARWIDTH,width,planesize);
+
+#if GRMODE == EGAGR
+		ShiftScore ();
+#endif
+		ob->needtoreact = true;
+		ob->temp3 = number;
+
+		changed = true;
+	}
+
+//
+// lives changed
+//
+	if (gamestate.lives != ob->temp4)
+	{
+		block = (spritetype _seg *)grsegs[SCOREBOXSPR];
+		width = block->width[0];
+		planesize = block->planesize[0];
+		dest = (byte far *)grsegs[SCOREBOXSPR]+block->sourceoffset[0]
+			+ planesize + width*20 + 2*CHARWIDTH;
+
+		if (gamestate.lives > 99)
+			strcpy (str,"99");
+		else
+			ltoa (gamestate.lives,str,10);
+
+		// erase leading spaces
+		length = strlen(str);
+		for (i=2;i>length;i--)
+			MemDrawChar (41,dest+=CHARWIDTH,width,planesize);
+
+		// draw digits
+		ch = str;
+		while (*ch)
+			MemDrawChar (*ch++ - '0'+42,dest+=CHARWIDTH,width,planesize);
+
+#if GRMODE == EGAGR
+		ShiftScore ();
+#endif
+		ob->needtoreact = true;
+		ob->temp4 = gamestate.lives;
+
+		changed = true;
+	}
+
+/*
+Note:
+-----
+
+It would be more efficient to use
+
+	if (changed)
+		ShiftScore();
+
+here instead of the individual ShiftScore() calls above. Because if the player
+gains a life by collecting points items, both the score and lives numbers need
+to be updated, which means the sprite would be shifted twice. And if the player
+fires a shot during the same frame, the ammo number also needs to be updated,
+leading to up to three shifts in one frame.
+*/
+
+	if (ob->x != originxglobal || ob->y != originyglobal)
+	{
+		ob->x = originxglobal;
+		ob->y = originyglobal;
+		changed = true;
+	}
+
+	if (changed)
+#if GRMODE == EGAGR
+		RF_PlaceSprite(&ob->sprite, ob->x+4*PIXGLOBAL, ob->y+4*PIXGLOBAL, SCOREBOXSPR, spritedraw, 3);
+#elif GRMODE == CGAGR
+		RF_PlaceSprite(&ob->sprite, ob->x+8*PIXGLOBAL, ob->y+8*PIXGLOBAL, SCOREBOXSPR, spritedraw, 3);
+#endif
+}
+
+/*
+===============
+=
+= DrawDemoPlaque
+=
+===============
+*/
+
+void DrawDemoPlaque(objtype *ob)
+{
+	if (ob->x != originxglobal || ob->y != originyglobal)
+	{
+		ob->x = originxglobal;
+		ob->y = originyglobal;
+		RF_PlaceSprite(&ob->sprite, ob->x + 160*PIXGLOBAL - 32*PIXGLOBAL, ob->y + 8*PIXGLOBAL, DEMOPLAQUESPR, spritedraw, 3);
+	}
+}
+
+
+/*
+=============================================================================
+
+							   MINI KEEN
+
+player->temp1 = dir
+player->temp2 = animation stage
+
+=============================================================================
+*/
+
+#ifdef KEEN4
+statetype s_keenonfoot1 = {WOLRDKEENRIDE1SPR, WOLRDKEENRIDE1SPR, stepthink, false, false, 30, 0, 0, T_FootFly, NULL, R_Draw, &s_keenonfoot2};
+statetype s_keenonfoot2 = {WOLRDKEENRIDE2SPR, WOLRDKEENRIDE2SPR, stepthink, false, false, 30, 0, 0, T_FootFly, NULL, R_Draw, &s_keenonfoot1};
+statetype s_worldswim = {0, 0, slide, true, false, 6, 16, 16, T_KeenWorldSwim, NULL, R_Draw, &s_worldswim};
+#endif
+
+#ifdef KEEN5
+statetype s_worldelevate = {-1, -1, think, true, false, 6, 16, 16, T_Elevate, NULL, R_Draw, NULL};
+#endif
+
+statetype s_worldkeen     = {0, 0, stepthink, false, false, 360, 0, 0, T_KeenWorld, NULL, R_Draw, &s_worldkeenwave1};
+
+statetype s_worldkeenwave1 = {WORLDKEENWAVE1SPR, WORLDKEENWAVE1SPR, stepthink, false, false, 20, 0, 0, T_KeenWorld, NULL, R_Draw, &s_worldkeenwave2};
+statetype s_worldkeenwave2 = {WORLDKEENWAVE2SPR, WORLDKEENWAVE2SPR, stepthink, false, false, 20, 0, 0, T_KeenWorld, NULL, R_Draw, &s_worldkeenwave3};
+statetype s_worldkeenwave3 = {WORLDKEENWAVE1SPR, WORLDKEENWAVE1SPR, stepthink, false, false, 20, 0, 0, T_KeenWorld, NULL, R_Draw, &s_worldkeenwave4};
+statetype s_worldkeenwave4 = {WORLDKEENWAVE2SPR, WORLDKEENWAVE2SPR, stepthink, false, false, 20, 0, 0, T_KeenWorld, NULL, R_Draw, &s_worldkeenwave5};
+statetype s_worldkeenwave5 = {WORLDKEENWAVE1SPR, WORLDKEENWAVE1SPR, stepthink, false, false, 20, 0, 0, T_KeenWorldWalk, NULL, R_Draw, &s_worldkeen};
+
+statetype s_worldkeenwalk = {0, 0, slide, true, false, 4, 24, 24, T_KeenWorldWalk, NULL, R_Draw, &s_worldkeenwalk};
+
+Sint16 worldshapes[8] = {WORLDKEENU1SPR-1, WORLDKEENUR1SPR-1, WORLDKEENR1SPR-1, WORLDKEENDR1SPR-1, WORLDKEEND1SPR-1, WORLDKEENDL1SPR-1, WORLDKEENL1SPR-1, WORLDKEENUL1SPR-1};	//-1 to everything because worldanims values are 1-based
+Sint16 worldanims[4] = {2, 3, 1, 3};
+#ifdef KEEN4
+Sint16 swimshapes[8] = {WORLDKEENSWIMU1SPR, WORLDKEENSWIMUR1SPR, WORLDKEENSWIMR1SPR, WORLDKEENSWIMDR1SPR, WORLDKEENSWIMD1SPR, WORLDKEENSWIMDL1SPR, WORLDKEENSWIML1SPR, WORLDKEENSWIMUL1SPR};
+#endif
+#ifndef KEEN6
+Sint16 tiledir[4] = {dir_South, dir_West, dir_North, dir_East};
+#endif
+
+/*
+======================
+=
+= SpawnWorldKeen
+=
+======================
+*/
+
+void SpawnWorldKeen(Sint16 x, Sint16 y)
+{
+#ifdef KEEN4
+	if (playstate == ex_foot)
+	{
+		player->needtoclip = cl_noclip;
+		player->obclass = keenobj;
+		player->x = gamestate.worldx;
+		player->y = gamestate.worldy;
+		player->active = ac_allways;
+		player->priority = 3;
+		player->xdir = 0;
+		player->ydir = 0;
+		if (gamestate.worldx < 20*TILEGLOBAL)
+		{
+			player->temp1 = 280;
+			player->xspeed = (30*TILEGLOBAL - player->x)/280 + 1;
+			player->yspeed = (55*TILEGLOBAL - player->y)/280 + 1;
+		}
+		else
+		{
+			player->temp1 = 140;
+			player->xspeed = (Sint16)(16*TILEGLOBAL - player->x)/140 + 1;
+			player->yspeed = (Sint16)(47*TILEGLOBAL - player->y)/140 + 1;
+		}
+		NewState(player, &s_keenonfoot1);
+		return;
+	}
+#endif
+
+	player->obclass = keenobj;
+	if (gamestate.worldx == 0)
+	{
+		player->x = CONVERT_TILE_TO_GLOBAL(x);
+		player->y = CONVERT_TILE_TO_GLOBAL(y);
+	}
+	else
+	{
+		player->x = gamestate.worldx;
+		player->y = gamestate.worldy;
+	}
+	player->active = ac_allways;
+	player->priority = 1;
+	player->xdir = 0;
+	player->ydir = 0;
+	player->temp1 = dir_West;
+	player->temp2 = 3;
+	player->temp3 = 0;
+	player->shapenum = WORLDKEENL3SPR;
+	NewState(player, &s_worldkeen);
+}
+
+#ifdef KEEN5
+/*
+======================
+=
+= SpawnWorldKeenPort
+=
+======================
+*/
+
+void SpawnWorldKeenPort(Uint16 tileX, Uint16 tileY)
+{
+	player->obclass = keenobj;
+	player->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	player->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	player->active = ac_allways;
+	player->priority = 1;
+	player->xdir = 0;
+	player->ydir = 0;
+	player->temp1 = dir_West;
+	player->temp2 = 3;
+	player->temp3 = 0;
+	player->shapenum = WORLDKEENL3SPR;
+	NewState(player, &s_worldkeen);
+}
+#endif
+
+
+/*
+======================
+=
+= CheckEnterLevel
+=
+======================
+*/
+
+void CheckEnterLevel(objtype *ob)
+{
+	Uint16 x, y, info;
+
+	for (y = ob->tiletop; y <= ob->tilebottom; y++)
+	{
+		for (x = ob->tileleft; x <= ob->tileright; x++)
+		{
+			info = *(mapsegs[2]+mapbwidthtable[y]/2 + x);
+			if (info > 0xC000 && info <= (0xC000 + 18))
+			{
+				gamestate.worldx = ob->x;
+				gamestate.worldy = ob->y;
+				gamestate.mapon = info - 0xC000;
+				playstate = ex_completed;
+				SD_PlaySound(SND_ENTERLEVEL);
+			}
+		}
+	}
+}
+
+/*
+======================
+=
+= T_KeenWorld
+=
+======================
+*/
+
+void T_KeenWorld(objtype *ob)
+{
+	if (c.dir != dir_None)
+	{
+		ob->state = &s_worldkeenwalk;
+		ob->temp2 = 0;
+		T_KeenWorldWalk(ob);
+	}
+	if (jumpbutton || pogobutton || firebutton)
+	{
+		CheckEnterLevel(ob);
+	}
+}
+
+/*
+======================
+=
+= T_KeenWorldWalk
+=
+======================
+*/
+
+void T_KeenWorldWalk(objtype *ob)
+{
+	if (ob->temp3)
+	{
+		ob->temp3 -= 4;
+		if (ob->temp3 < 0)
+			ob->temp3 = 0;
+	}
+	else
+	{
+		ob->xdir = c.xaxis;
+		ob->ydir = c.yaxis;
+		if (pogobutton || firebutton || jumpbutton)
+		{
+			CheckEnterLevel(ob);
+		}
+		if (c.dir == dir_None)
+		{
+			ob->state = &s_worldkeen;
+			ob->shapenum = worldshapes[ob->temp1] + 3;
+			return;
+		}
+		ob->temp1 = c.dir;
+	}
+	if (++ob->temp2 == 4)
+		ob->temp2 = 0;
+	ob->shapenum = worldshapes[ob->temp1] + worldanims[ob->temp2];
+
+	if (ob->temp2 == 1)
+	{
+		SD_PlaySound(SND_WORLDWALK1);
+	}
+	else if (ob->temp2 == 3)
+	{
+		SD_PlaySound(SND_WORLDWALK2);
+	}
+}
+
+#ifdef KEEN4
+/*
+======================
+=
+= T_FootFly
+=
+======================
+*/
+
+void T_FootFly(objtype *ob)
+{
+	ob->temp1 = ob->temp1 - tics;
+	xtry = ob->xspeed * tics;
+	ytry = ob->yspeed * tics;
+	if (ob->temp1 <= 0)
+	{
+		xtry -= ob->xspeed * -ob->temp1;
+		ytry -= ob->yspeed * -ob->temp1;
+		ob->priority = 1;
+		ob->temp1 = dir_West;
+		ob->temp2 = 3;
+		ob->temp3 = 0;
+		player->xdir = 0;
+		player->ydir = 0;
+		ob->state = &s_worldkeen;
+		ob->shapenum = WORLDKEENL3SPR;
+		ob->needtoclip = cl_midclip;
+	}
+}
+
+/*
+======================
+=
+= T_KeenWorldSwim
+=
+======================
+*/
+
+void T_KeenWorldSwim(objtype *ob)
+{
+	if (ob->temp3)
+	{
+		ob->temp3 -= 6;
+		if (ob->temp3 < 0)
+			ob->temp3 = 0;
+	}
+	else
+	{
+		ob->xdir = c.xaxis;
+		ob->ydir = c.yaxis;
+		if (c.xaxis || c.yaxis)
+			ob->temp1 = c.dir;
+	}
+	ob->shapenum = swimshapes[ob->temp1] + ob->temp2;
+	if (++ob->temp2 == 2)
+		ob->temp2 = 0;
+
+	if (ob->temp2 == 0)
+	{
+		SD_PlaySound(SND_SWIM1);
+	}
+	else
+	{
+		SD_PlaySound(SND_SWIM2);
+	}
+}
+
+#else	// NOT Keen 4 (i.e. Keen 5 & 6):
+
+/*
+======================
+=
+= Teleport
+=
+======================
+*/
+
+void Teleport(Uint16 tileX, Uint16 tileY)
+{
+	Uint16 tile, globalx, globaly, duration, move;
+	objtype *o;
+	objtype *ob = player;
+
+	//
+	// enter the teleporter
+	//
+	SD_PlaySound(SND_TELEPORT);
+	globalx = CONVERT_TILE_TO_GLOBAL(tileX);
+	globaly = CONVERT_TILE_TO_GLOBAL(tileY);
+
+#ifdef KEEN6Ev15
+	// We need to make the compiler "forget" that duration starts at 0
+	// to make sure the while-loop check is performed when entering the
+	// loop. Can't change compiler settings since we do need that loop
+	// optimization for the for-loop at the end of this routine.
+	if (true)
+		duration = 0;
+#else
+	duration = 0;
+#endif
+
+	while (duration < 130)
+	{
+		RF_Refresh();
+		move = tics*2;
+		duration += tics;
+
+		if (ob->x == globalx && ob->y == globaly)
+			break;
+
+		if (ob->y < globaly)
+		{
+			ob->y += move;
+			if (ob->y > globaly)
+				ob->y = globaly;
+		}
+		else if (ob->y > globaly)
+		{
+			ob->y -= move;
+			if (ob->y < globaly)
+				ob->y = globaly;
+		}
+
+		if (ob->x < globalx)
+		{
+			ob->x += move;
+			if (ob->x > globalx)
+				ob->x = globalx;
+		}
+		else if (ob->x > globalx)
+		{
+			ob->x -= move;
+			if (ob->x < globalx)
+				ob->x = globalx;
+		}
+
+		ob->shapenum = ((TimeCount >> 3) % 3) + WORLDKEENU1SPR;
+		RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+
+		tile = ((TimeCount >> 2) & TELEPORERTILEMASK) + TELEPORTERTILE1;
+		RF_MemToMap(&tile, 1, tileX, tileY, 1, 1);
+	}
+
+	tile = TELEPORTERTILE2;
+	RF_MemToMap(&tile, 1, tileX, tileY, 1, 1);
+
+	//
+	// teleport to new location
+	//
+	tile = *(mapsegs[2]+mapbwidthtable[tileY]/2 + tileX);
+	tileX = tile >> 8;
+	tileY = tile & 0x7F;	// BUG? y coordinate is limited to 1..127
+	ob->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	ob->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	ob->xdir = 0;
+	ob->ydir = 1;
+	ob->temp1 = dir_South;
+	NewState(ob, ob->state);
+	CenterActor(ob);
+
+	//
+	// draw flags/signs for new location
+	//
+	for (o=player->next; o; o=o->next)
+	{
+		if (!o->active && o->obclass == flagobj
+			&& o->tileright >= originxtile-1 && o->tileleft <= originxtilemax+1
+			&& o->tiletop <= originytilemax+1 && o->tilebottom >= originytile-1)
+		{
+			o->needtoreact = true;
+			o->active = ac_yes;
+			RF_PlaceSprite(&o->sprite, o->x, o->y, o->shapenum, spritedraw, o->priority);
+		}
+	}
+	UpdateScore(scoreobj);
+	RF_Refresh();
+	RF_Refresh();
+
+	//
+	// leave teleporter
+	//
+	SD_PlaySound(SND_TELEPORT);
+
+	for (duration = 0; duration < 90; )
+	{
+		RF_Refresh();
+		duration += tics;
+		ob->y += tics*2 + tics;
+
+		ob->shapenum = ((TimeCount >> 3) % 3) + WORLDKEEND1SPR;
+		RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+
+		tile = ((TimeCount >> 2) & TELEPORERTILEMASK) + TELEPORTERTILE3;
+		RF_MemToMap(&tile, 1, tileX, tileY, 1, 1);
+	}
+
+	tile = TELEPORTERTILE4;
+	RF_MemToMap(&tile, 1, tileX, tileY, 1, 1);
+	xtry = ytry = 0;
+	ClipToWalls(ob);
+}
+
+#ifdef KEEN5
+
+/*
+======================
+=
+= T_Elevate
+=
+======================
+*/
+
+void T_Elevate(objtype *ob)
+{
+	Sint16 i, x, y, tx, ty;
+	Uint16 tiles[2][2];
+
+	ytry = ob->ydir * 64 * tics;
+	if (ob->x != ob->temp2)
+	{
+		xtry = ob->xdir * 12 * tics;
+		if ( (ob->xdir == 1 && ob->x + xtry > ob->temp2)
+			|| (ob->xdir == -1 && ob->x + xtry < ob->temp2) )
+		{
+			xtry = ob->temp2 - ob->x;
+		}
+	}
+
+	//
+	// Keen has no sprite in this state, so we need to update the hitbox manually
+	// to avoid issues (the screen scrolling routines use left/right/top/bottom)
+	//
+	ob->left = ob->x + xtry;
+	ob->right = ob->left + (TILEGLOBAL-1);
+	ob->top = ob->y + ytry;
+	ob->bottom = ob->top + (TILEGLOBAL-1);
+
+	if (ob->ydir == 1)
+	{
+		if (ob->y + ytry < ob->temp1)
+			return;
+	}
+	else
+	{
+		if (ob->y + ytry > ob->temp1)
+			return;
+	}
+
+	//
+	// the invisible Keen has arrived at its destination
+	//
+	ytry = 0;
+	xtry = 0;
+	ob->x = ob->temp2;
+	ob->y = ob->temp1;
+	ob->priority = 1;
+	ob->temp1 = 4;
+	ob->temp2 = 3;
+	ob->temp3 = 0;
+	player->xdir = 0;
+	player->ydir = 0;
+	ob->state = &s_worldkeen;
+	ob->shapenum = WORLDKEEND3SPR;
+	ob->needtoclip = cl_midclip;
+	tx = CONVERT_GLOBAL_TO_TILE(ob->x);
+	ty = CONVERT_GLOBAL_TO_TILE(ob->y);
+	WorldScrollScreen(ob);
+	UpdateScore(scoreobj);
+	RF_Refresh();
+	RF_Refresh();
+
+	ob->y -= TILEGLOBAL;
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+
+	//
+	// open the elevator door
+	//
+	SD_PlaySound(SND_ELEVATORDOOR);
+	for (i=0; i<=5; i++)
+	{
+		for (y=0; y<2; y++)
+		{
+			for (x=0; x<2; x++)
+			{
+				tiles[y][x] = *(mapsegs[1]+mapbwidthtable[y]/2 + i*2 + x);
+			}
+		}
+		RF_MemToMap(&tiles[0][0], 1, tx, ty-2, 2, 2);
+		RF_Refresh();
+		VW_WaitVBL(8);
+	}
+
+	//
+	// make Keen walk out of the elevator
+	//
+	for (y=0; y<32; y++)
+	{
+		ob->y += 8;	// move half a pixel every frame for 32 frames -> move down 16 pixels total
+		ob->shapenum = (y / 4) % 3 + WORLDKEEND1SPR;
+		RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+		RF_Refresh();
+	}
+	ob->needtoclip = cl_midclip;	// redundant, but doesn't do any harm
+}
+
+/*
+======================
+=
+= Elevator
+=
+======================
+*/
+
+void Elevator(Uint16 tileX, Uint16 tileY, Sint16 dir)
+{
+	Uint16 info, globalx, globaly, duration, move;
+	Sint16 x, y, i;
+	Uint16 tiles[2][2];
+	objtype *ob = player;
+
+	globalx = CONVERT_TILE_TO_GLOBAL(tileX);
+	globaly = CONVERT_TILE_TO_GLOBAL(tileY);
+
+	//
+	// make Keen walk into the elevator
+	//
+	for (duration = 0; duration < 130; )
+	{
+		CalcBounds(ob);
+		WorldScrollScreen(ob);
+		UpdateScore(scoreobj);
+		RF_Refresh();
+
+		move = tics * 2;
+		duration += tics;
+
+		if (ob->x == globalx && ob->y == globaly)
+			break;
+
+		if (ob->y < globaly)
+		{
+			ob->y += move;
+			if (ob->y > globaly)
+				ob->y = globaly;
+		}
+		else if (ob->y > globaly)
+		{
+			ob->y -= move;
+			if (ob->y < globaly)
+				ob->y = globaly;
+		}
+
+		if (ob->x < globalx)
+		{
+			ob->x += move;
+			if (ob->x > globalx)
+				ob->x = globalx;
+		}
+		else if (ob->x > globalx)
+		{
+			ob->x -= move;
+			if (ob->x < globalx)
+				ob->x = globalx;
+		}
+
+		ob->shapenum = ((duration / 8) % 3) + WORLDKEENU1SPR;
+		RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+	}
+
+	//
+	// close the elevator door
+	//
+	SD_PlaySound(SND_ELEVATORDOOR);
+	for (i=5; i >= 0; i--)
+	{
+		for (y=0; y<2; y++)
+		{
+			for (x=0; x<2; x++)
+			{
+				tiles[y][x] = *(mapsegs[1]+mapbwidthtable[y]/2 + i*2 + x);
+			}
+		}
+		RF_MemToMap(&tiles[0][0], 1, tileX+dir, tileY-1, 2, 2);
+		RF_Refresh();
+		VW_WaitVBL(8);
+	}
+
+	//
+	// make Keen invisible (and not clipping) and send him to the destination
+	//
+	RF_RemoveSprite(&ob->sprite);
+	info = *(mapsegs[2] + mapbwidthtable[tileY]/2 + tileX);
+	ob->temp2 = CONVERT_TILE_TO_GLOBAL(info >> 8);
+	ob->temp1 = CONVERT_TILE_TO_GLOBAL((info & 0x7F) + 1);	// BUG? y coordinate is limited to 1..127
+	if (ob->temp1 < ob->y)
+	{
+		ob->ydir = -1;
+	}
+	else
+	{
+		ob->ydir = 1;
+	}
+	if (ob->temp2 < ob->x)
+	{
+		ob->xdir = -1;
+	}
+	else
+	{
+		ob->xdir = 1;
+	}
+	ob->needtoclip = cl_noclip;
+	ob->state = &s_worldelevate;
+}
+
+#endif	//ifdef KEEN5
+
+#endif	//ifdef KEEN4 ... else ...
+
+/*
+======================
+=
+= CheckWorldInTiles
+=
+======================
+*/
+
+void CheckWorldInTiles(objtype *ob)
+{
+	Uint16 tx, ty, intile;
+
+	if (ob->temp3)
+		return;
+
+	tx = ob->tilemidx;
+	ty = CONVERT_GLOBAL_TO_TILE(ob->top + (ob->bottom-ob->top)/2);
+	intile = tinf[INTILE + *(mapsegs[1]+mapbwidthtable[ty]/2+tx)];
+#if defined KEEN4
+	if (intile == INTILE_SHORESOUTH || intile == INTILE_SHORENORTH
+		|| intile == INTILE_SHOREEAST || intile == INTILE_SHOREWEST)
+	{
+		if (!gamestate.wetsuit)
+		{
+			SD_PlaySound(SND_NOWAY);
+			CantSwim();
+			RF_ForceRefresh();
+			xtry = -ob->xmove;
+			ytry = -ob->ymove;
+			ob->xdir = ob->ydir = 0;
+			ClipToWalls(ob);
+		}
+		else
+		{
+			ob->temp1 = tiledir[intile-INTILE_SHORESOUTH];
+			if (ob->state == &s_worldswim)
+			{
+				ob->temp1 = opposite[ob->temp1];
+			}
+			switch (ob->temp1)
+			{
+			case dir_North:
+				ob->xdir = 0;
+				ob->ydir = -1;
+				break;
+			case dir_East:
+				ob->xdir = 1;
+				ob->ydir = 0;
+				break;
+			case dir_South:
+				ob->xdir = 0;
+				ob->ydir = 1;
+				break;
+			case dir_West:
+				ob->xdir = -1;
+				ob->ydir = 0;
+				break;
+			}
+			ob->temp2 = 0;
+			ob->temp3 = 18;
+			if (ob->state == &s_worldswim)
+			{
+				ChangeState(ob, &s_worldkeenwalk);
+			}
+			else
+			{
+				ChangeState(ob, &s_worldswim);
+			}
+		}
+	}
+#elif defined KEEN5
+	switch (intile)
+	{
+	case INTILE_TELEPORT:
+		Teleport(tx, ty);
+		break;
+	case INTILE_ELEVATORLEFT:
+		Elevator(tx, ty, 0);
+		break;
+	case INTILE_ELEVATORRIGHT:
+		Elevator(tx, ty, -1);
+		break;
+	}
+#elif defined KEEN6
+	switch (intile)
+	{
+	case INTILE_TELEPORT:
+		Teleport(tx, ty);
+		break;
+	}
+#endif
+}
+
+/*
+=============================================================================
+
+							   FLAGS
+
+temp1 = x destination for the thrown flag
+temp2 = y destination for the thrown flag
+temp3 = amount of time passed since flag was thrown (in tics)
+
+=============================================================================
+*/
+
+statetype s_flagwave1     = {FLAGFLAP1SPR, FLAGFLAP1SPR, step, false, false, 10, 0, 0, NULL, NULL, R_Draw, &s_flagwave2};
+statetype s_flagwave2     = {FLAGFLAP2SPR, FLAGFLAP2SPR, step, false, false, 10, 0, 0, NULL, NULL, R_Draw, &s_flagwave3};
+statetype s_flagwave3     = {FLAGFLAP3SPR, FLAGFLAP3SPR, step, false, false, 10, 0, 0, NULL, NULL, R_Draw, &s_flagwave4};
+statetype s_flagwave4     = {FLAGFLAP4SPR, FLAGFLAP4SPR, step, false, false, 10, 0, 0, NULL, NULL, R_Draw, &s_flagwave1};
+
+#ifndef KEEN5
+statetype s_throwflag0    = {FLAGFLIP1SPR, FLAGFLIP1SPR, think, false, false, 6, 0, 0, TossThink, NULL, R_Draw, &s_throwflag1};
+statetype s_throwflag1    = {FLAGFLIP1SPR, FLAGFLIP1SPR, stepthink, false, false, 12, 0, 0, PathThink, NULL, R_Draw, &s_throwflag2};
+statetype s_throwflag2    = {FLAGFLIP2SPR, FLAGFLIP2SPR, stepthink, false, false, 12, 0, 0, PathThink, NULL, R_Draw, &s_throwflag3};
+statetype s_throwflag3    = {FLAGFLIP3SPR, FLAGFLIP3SPR, stepthink, false, false, 12, 0, 0, PathThink, NULL, R_Draw, &s_throwflag4};
+statetype s_throwflag4    = {FLAGFLIP4SPR, FLAGFLIP4SPR, stepthink, false, false, 12, 0, 0, PathThink, NULL, R_Draw, &s_throwflag5};
+statetype s_throwflag5    = {FLAGFALL1SPR, FLAGFALL1SPR, stepthink, false, false, 12, 0, 0, PathThink, NULL, R_Draw, &s_throwflag6};
+statetype s_throwflag6    = {FLAGFALL1SPR, FLAGFALL1SPR, stepthink, true, false, 1, 0, 0, FlagAlign, NULL, R_Draw, &s_flagwave1};
+#endif
+
+Sint16 flagx, flagy;
+Point flagpath[30];
+
+/*
+======================
+=
+= SpawnFlag
+=
+======================
+*/
+
+void SpawnFlag(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->needtoclip = cl_noclip;
+	new->priority = 3;
+	new->obclass = flagobj;
+	new->active = ac_yes;
+#if defined KEEN4
+	new->x = CONVERT_TILE_TO_GLOBAL(x) + 6*PIXGLOBAL;
+	new->y = CONVERT_TILE_TO_GLOBAL(y) + -30*PIXGLOBAL;
+#elif defined KEEN5
+	new->x = CONVERT_TILE_TO_GLOBAL(x) + -5*PIXGLOBAL;
+	new->y = CONVERT_TILE_TO_GLOBAL(y) + -30*PIXGLOBAL;
+#elif defined KEEN6
+	new->x = CONVERT_TILE_TO_GLOBAL(x) + 6*PIXGLOBAL;		// useless!
+	new->y = CONVERT_TILE_TO_GLOBAL(y) + -30*PIXGLOBAL;	// useless!
+#if GRMODE == CGAGR
+	new->x = CONVERT_TILE_TO_GLOBAL(x) + 10*PIXGLOBAL;
+#else
+	new->x = CONVERT_TILE_TO_GLOBAL(x) + 14*PIXGLOBAL;
+#endif
+	new->y = CONVERT_TILE_TO_GLOBAL(y) + -26*PIXGLOBAL;
+	{
+		Uint16 tile = *(mapsegs[1]+mapbwidthtable[y]/2 + x) + 1;
+		RF_MemToMap(&tile, 1, x, y, 1, 1);
+	}
+#endif
+	new->ticcount = US_RndT() / 16;
+	NewState(new, &s_flagwave1);
+}
+
+#ifndef KEEN5
+/*
+======================
+=
+= SpawnThrowFlag
+=
+======================
+*/
+
+void SpawnThrowFlag(Sint16 x, Sint16 y)
+{
+	Sint16 i;
+	Sint32 xdist, ydist;
+
+	GetNewObj(false);
+	new->needtoclip = cl_noclip;
+	new->priority = 3;
+	new->obclass = flagobj;
+	new->active = ac_allways;
+	new->x = gamestate.worldx - 16*PIXGLOBAL;
+	new->y = gamestate.worldy - 16*PIXGLOBAL;
+#if defined KEEN4
+	new->temp1 = CONVERT_TILE_TO_GLOBAL(x) + 6*PIXGLOBAL;
+	new->temp2 = CONVERT_TILE_TO_GLOBAL(y) + -38*PIXGLOBAL;
+#elif defined KEEN6
+	flagx = x;
+	flagy = y;
+#if GRMODE == CGAGR
+	new->temp1 = CONVERT_TILE_TO_GLOBAL(x) + 10*PIXGLOBAL;
+#else
+	new->temp1 = CONVERT_TILE_TO_GLOBAL(x) + 14*PIXGLOBAL;
+#endif
+	new->temp2 = CONVERT_TILE_TO_GLOBAL(y) + -34*PIXGLOBAL;
+#endif
+	xdist = (Sint32)new->temp1 - (Sint32)new->x;
+	ydist = (Sint32)new->temp2 - (Sint32)new->y;
+	for (i = 0; i < 30; i++)
+	{
+		flagpath[i].x = new->x + (xdist * min(i, 24))/24;
+		flagpath[i].y = new->y + (ydist * i)/30;
+		if (i < 10)
+		{
+			flagpath[i].y -= i*3*PIXGLOBAL;
+		}
+		else if (i < 15)
+		{
+			flagpath[i].y -= i*PIXGLOBAL + 20*PIXGLOBAL;
+		}
+		else if (i < 20)
+		{
+			flagpath[i].y -= (20-i)*PIXGLOBAL + 30*PIXGLOBAL;
+		}
+		else
+		{
+			flagpath[i].y -= (29-i)*3*PIXGLOBAL;
+		}
+	}
+	NewState(new, &s_throwflag0);
+}
+
+/*
+======================
+=
+= TossThink
+=
+======================
+*/
+
+void TossThink(objtype *ob)
+{
+	if (screenfaded)
+		return;
+
+	SD_StopSound();
+	SD_PlaySound(SND_FLAGSPIN);
+	ob->state = ob->state->nextstate;
+}
+
+/*
+======================
+=
+= PathThink
+=
+======================
+*/
+
+void PathThink(objtype *ob)
+{
+	ob->temp3 = ob->temp3 + tics;
+	if (ob->temp3 > 58)
+		ob->temp3 = 58;
+
+	ob->x = flagpath[ob->temp3/2].x;
+	ob->y = flagpath[ob->temp3/2].y;
+	ob->needtoreact = true;
+	if (ob->temp1 == 0)
+	{
+		SD_PlaySound(SND_FLAGSPIN);
+	}
+}
+
+/*
+======================
+=
+= FlagAlign
+=
+======================
+*/
+
+void FlagAlign(objtype *ob)
+{
+	ob->x = ob->temp1;
+	ob->y = ob->temp2 + 8*PIXGLOBAL;
+	SD_PlaySound(SND_FLAGLAND);
+#ifdef KEEN6
+	{
+		Uint16 tile = *(mapsegs[1]+mapbwidthtable[flagy]/2 + flagx) + 1;
+		RF_MemToMap(&tile, 1, flagx, flagy, 1, 1);
+	}
+#endif
+}
+#endif
+
+/*
+=============================================================================
+
+						 NEURAL STUNNER
+
+=============================================================================
+*/
+statetype s_stunray1 = {STUN1SPR, STUN1SPR, slide, false, false, 6, 64, 64, T_Shot, NULL, R_Shot, &s_stunray2};
+statetype s_stunray2 = {STUN2SPR, STUN2SPR, slide, false, false, 6, 64, 64, T_Shot, NULL, R_Shot, &s_stunray3};
+statetype s_stunray3 = {STUN3SPR, STUN3SPR, slide, false, false, 6, 64, 64, T_Shot, NULL, R_Shot, &s_stunray4};
+statetype s_stunray4 = {STUN4SPR, STUN4SPR, slide, false, false, 6, 64, 64, T_Shot, NULL, R_Shot, &s_stunray1};
+
+statetype s_stunhit  = {STUNHIT1SPR, STUNHIT1SPR, step, false, false, 12, 0, 0, NULL, NULL, R_Draw, &s_stunhit2};
+statetype s_stunhit2 = {STUNHIT2SPR, STUNHIT2SPR, step, false, false, 12, 0, 0, NULL, NULL, R_Draw, NULL};
+
+/*
+======================
+=
+= SpawnShot
+=
+======================
+*/
+
+void SpawnShot(Uint16 x, Uint16 y, Direction dir)
+{
+	if (!gamestate.ammo)
+	{
+		SD_PlaySound(SND_USESWITCH);
+		return;
+	}
+
+	gamestate.ammo--;
+	GetNewObj(true);
+	new->x = x;
+	new->y = y;
+	new->priority = 0;
+	new->obclass = stunshotobj;
+	new->active = ac_allways;
+	SD_PlaySound(SND_KEENFIRE);
+	switch (dir)
+	{
+	case dir_North:
+		new->xdir = 0;
+		new->ydir = -1;
+		break;
+	case dir_East:
+		new->xdir = 1;
+		new->ydir = 0;
+		break;
+	case dir_South:
+		new->xdir = 0;
+		new->ydir = 1;
+		break;
+	case dir_West:
+		new->xdir = -1;
+		new->ydir = 0;
+		break;
+	default:
+		Quit("SpawnShot: Bad dir!");
+		break;
+	}
+	NewState(new, &s_stunray1);
+
+#ifdef KEEN6
+	{
+		objtype *ob;
+
+		for (ob=player->next; ob; ob=ob->next)
+		{
+			if (ob->active
+				&& new->right > ob->left && new->left < ob->right
+				&& new->top < ob->bottom && new->bottom > ob->top
+				&& ob->state->contact)
+			{
+				ob->state->contact(ob, new);
+				return;
+			}
+		}
+	}
+#endif
+}
+
+/*
+======================
+=
+= ExplodeShot
+=
+======================
+*/
+
+void ExplodeShot(objtype *ob)
+{
+	ob->obclass = inertobj;
+	ChangeState(ob, &s_stunhit);
+	SD_PlaySound(SND_SHOTEXPLODE);
+}
+
+/*
+======================
+=
+= T_Shot
+=
+======================
+*/
+
+void T_Shot(objtype *ob)
+{
+	objtype *ob2;
+
+	if (ob->tileright >= originxtile && ob->tilebottom >= originytile
+		&& ob->tileleft <= originxtilemax && ob->tiletop <= originytilemax)
+	{
+		//object is visible, so do nothing
+		return;
+	}
+
+	if (ob->tileright+10 < originxtile
+		|| ob->tileleft-10 > originxtilemax
+		|| ob->tilebottom+6 < originytile
+		|| ob->tiletop-6 > originytilemax)
+	{
+		//shot is off-screen by more than half a screen, so remove it
+		RemoveObj(ob);
+		return;
+	}
+
+	//check for collisions with INACTIVE objects
+	for (ob2 = player->next; ob2; ob2 = ob2->next)
+	{
+		if (!ob2->active && ob->right > ob2->left && ob->left < ob2->right
+			&& ob->top < ob2->bottom && ob->bottom > ob2->top)
+		{
+			if (ob2->state->contact)
+			{
+				ob2->state->contact(ob2, ob);
+				ob2->needtoreact = true;
+				ob2->active = ac_yes;
+			}
+
+			if (ob->obclass == nothing)	//BUG: obclass is 'inertobj' for the exploded shot
+				break;
+		}
+	}
+}
+
+/*
+======================
+=
+= R_Shot
+=
+======================
+*/
+
+void R_Shot(objtype *ob)
+{
+	Uint16 tile;
+
+	if (ob->hitnorth == 1 && ob->tileleft != ob->tileright)
+	{
+		tile = *(mapsegs[1]+mapbwidthtable[ob->tiletop-1]/2+ob->tileright);
+		if (tinf[NORTHWALL+tile] == 17)
+		{
+			ob->hitnorth = 17;
+			ob->x += 0x100 - (ob->x & 0xFF);
+		}
+	}
+	else if (ob->hitnorth == 17 && ob->tileleft != ob->tileright)
+	{
+		ob->x &= 0xFF00;
+	}
+	if (ob->hitsouth == 1 && ob->tileleft != ob->tileright)
+	{
+		tile = *(mapsegs[1]+mapbwidthtable[ob->tilebottom+1]/2+ob->tileright);
+		if (tinf[SOUTHWALL+tile] == 17)
+		{
+			ob->hitsouth = 17;
+			ob->x += 0x100 - (ob->x & 0xFF);
+		}
+	}
+	else if (ob->hitsouth == 17 && ob->tileleft != ob->tileright)
+	{
+		ob->x &= 0xFF00;
+	}
+	if (ob->hitnorth == 17 || ob->hitsouth == 17)
+	{
+		ytry = ob->state->ymove * tics * ob->ydir;
+		ob->y += ytry;
+		ob->top += ytry;
+		ob->bottom += ytry;
+		ob->tiletop = CONVERT_GLOBAL_TO_TILE(ob->top);
+		ob->tilebottom = CONVERT_GLOBAL_TO_TILE(ob->bottom);
+	}
+	else if (ob->hitnorth || ob->hitsouth || ob->hiteast || ob->hitwest)
+	{
+		ExplodeShot(ob);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+=============================================================================
+
+						 DOOR
+
+temp1 = height of the door's main section (identical tiles!), in tiles
+        DoorOpen changes two more tiles at the bottom end of the door
+		  (total door height in tiles is temp1 + 2)
+
+=============================================================================
+*/
+
+statetype s_door1    = {0, 0, step, false, false, 10, 0, 0, DoorOpen, NULL, NULL, &s_door2};
+statetype s_door2    = {0, 0, step, false, false, 10, 0, 0, DoorOpen, NULL, NULL, &s_door3};
+statetype s_door3    = {0, 0, step, false, false, 10, 0, 0, DoorOpen, NULL, NULL, NULL};
+
+/*
+======================
+=
+= DoorOpen
+=
+======================
+*/
+
+void DoorOpen(objtype *ob)
+{
+	Sint16 i;
+	Uint16 far *map;
+	Uint16 tiles[50];
+
+	map = mapsegs[1] + mapbwidthtable[ob->y]/2 + ob->x;
+	for (i=0; i < ob->temp1+2; i++, map+=mapwidth)
+	{
+		tiles[i] = *map + 1;
+	}
+	RF_MemToMap(tiles, 1, ob->x, ob->y, 1, ob->temp1+2);
+}
+
+#ifdef KEEN5
+/*
+=============================================================================
+
+						 CARD DOOR
+
+temp1 = frame counter
+
+=============================================================================
+*/
+statetype s_carddoor    = {0, 0, step, false, false, 15, 0, 0, CardDoorOpen, NULL, NULL, &s_carddoor};
+
+/*
+======================
+=
+= CardDoorOpen
+=
+======================
+*/
+
+void CardDoorOpen(objtype *ob)
+{
+	Sint16 x, y;
+	Uint16 far *map;
+	Uint16 tiles[16], *tileptr;
+
+	tileptr = tiles;
+	map = mapsegs[1] + mapbwidthtable[ob->y]/2 + ob->x;
+	for (y=0; y<4; y++, map+=mapwidth)
+	{
+		for (x=0; x<4; x++)
+		{
+			*tileptr++ = map[x]-4;
+		}
+	}
+	RF_MemToMap(tiles, 1, ob->x, ob->y, 4, 4);
+
+	if (++ob->temp1 == 3)
+		ob->state = NULL;
+}
+
+#endif
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/CK_MAIN.C b/16/keen456/KEEN4-6/CK_MAIN.C
new file mode 100755
index 00000000..b8e71538
--- /dev/null
+++ b/16/keen456/KEEN4-6/CK_MAIN.C
@@ -0,0 +1,531 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+// CK_MAIN.C
+/*
+=============================================================================
+
+							COMMANDER KEEN
+
+					An Id Software production
+
+=============================================================================
+*/
+
+#include "CK_DEF.H"
+
+/*
+=============================================================================
+
+						 GLOBAL VARIABLES
+
+=============================================================================
+*/
+
+boolean tedlevel;
+Uint16 tedlevelnum;
+
+char str[80], str2[20];
+boolean storedemo, jerk;
+
+/*
+=============================================================================
+
+						 LOCAL VARIABLES
+
+=============================================================================
+*/
+
+//===========================================================================
+
+/*
+=====================
+=
+= SizeText
+=
+= Calculates width and height of a string that contains line breaks
+= (Note: only the height is ever used, width is NOT calculated correctly)
+=
+=====================
+*/
+
+void SizeText(char *text, Uint16 *width, Uint16 *height)
+{
+	register char *ptr;
+	char c;
+	Uint16 w, h;
+	char strbuf[80];
+
+	*width = *height = 0;
+	ptr = &strbuf[0];
+	while ((c=*(text++)) != '\0')
+	{
+		*(ptr++) = c;
+		if (c == '\n' || !*text)
+		{
+			USL_MeasureString(strbuf, &w, &h);	// BUG: strbuf may not have a terminating '\0' at the end!
+			*height += h;
+			if (*width < w)
+			{
+				*width = w;
+			}
+			ptr = &strbuf[0];
+		}
+	}
+}
+
+//===========================================================================
+
+/*
+==========================
+=
+= ShutdownId
+=
+= Shuts down all ID_?? managers
+=
+==========================
+*/
+
+void ShutdownId(void)
+{
+	US_Shutdown();
+	SD_Shutdown();
+	IN_Shutdown();
+	RF_Shutdown();
+	VW_Shutdown();
+	CA_Shutdown();
+	MM_Shutdown();
+}
+
+
+//===========================================================================
+
+/*
+==========================
+=
+= InitGame
+=
+= Load a few things right away
+=
+==========================
+*/
+
+void InitGame(void)
+{
+	static char *ParmStrings[] = {"JERK", ""};
+	void MML_UseSpace (Uint16 segstart, Uint16 seglength);
+
+	Uint16 segstart,seglength;
+	Sint16 i;
+
+	// Note: The value of the jerk variable is replaced with the value
+	// read from the config file during US_Startup, which means the
+	// JERK parameter has absolutely no effect if a valid config file
+	// exists. The parameter check should be moved to some place after
+	// US_Startup to make it work reliably.
+	
+	for (i=1; i < _argc; i++)
+	{
+		if (US_CheckParm(_argv[i], ParmStrings) == 0)
+		{
+			jerk = true;
+		}
+	}
+
+	US_TextScreen();
+
+	MM_Startup();
+	VW_Startup();
+	RF_Startup();
+	IN_Startup();
+	SD_Startup();
+	US_Startup();
+
+	US_UpdateTextScreen();
+
+	CA_Startup();
+	US_Setup();
+
+	US_SetLoadSaveHooks(&LoadTheGame, &SaveTheGame, &ResetGame);
+	drawcachebox = DialogDraw;
+	updatecachebox = DialogUpdate;
+	finishcachebox = DialogFinish;
+
+//
+// load in and lock down some basic chunks
+//
+
+	CA_ClearMarks();
+
+	CA_MarkGrChunk(STARTFONT);
+	CA_MarkGrChunk(STARTTILE8);
+	CA_MarkGrChunk(STARTTILE8M);
+#if GRMODE == EGAGR
+	CA_MarkGrChunk(CORDPICM);
+	CA_MarkGrChunk(METALPOLEPICM);
+#endif
+
+	CA_CacheMarks(NULL);
+
+	MM_SetLock(&grsegs[STARTFONT], true);
+	MM_SetLock(&grsegs[STARTTILE8], true);
+	MM_SetLock(&grsegs[STARTTILE8M], true);
+#if GRMODE == EGAGR
+	MM_SetLock(&grsegs[CORDPICM], true);
+	MM_SetLock(&grsegs[METALPOLEPICM], true);
+#endif
+
+	fontcolor = WHITE;
+
+	US_FinishTextScreen();
+
+//
+// reclaim the memory from the linked in text screen
+//
+	segstart = FP_SEG(&introscn);
+	seglength = 4000/16;
+	if (FP_OFF(&introscn))
+	{
+		segstart++;
+		seglength--;
+	}
+	MML_UseSpace (segstart,seglength);
+
+	VW_SetScreenMode(GRMODE);
+#if GRMODE == CGAGR
+	VW_ColorBorder(BROWN);
+#else
+	VW_ColorBorder(CYAN);
+#endif
+	VW_ClearVideo(BLACK);
+}
+
+//===========================================================================
+
+/*
+==========================
+=
+= Quit
+=
+==========================
+*/
+
+void Quit(char *error)
+{
+	Uint16 finscreen;
+
+	if (!error)
+	{
+		CA_SetAllPurge();
+		CA_CacheGrChunk(ORDERSCREEN);
+		finscreen = (Uint16)grsegs[ORDERSCREEN];
+	}
+
+	// BUG: VW_ClearVideo may brick the system if screenseg is 0
+	// (i.e. VW_SetScreenMode has not been executed) - this may
+	// happen if the code runs into an error during InitGame
+	// (EMS/XMS errors, files not found etc.)
+	VW_ClearVideo(BLACK);
+	VW_SetLineWidth(40);
+
+	ShutdownId();
+	if (error && *error)
+	{
+		puts(error);
+		if (tedlevel)
+		{
+			getch();
+			execlp("TED5.EXE", "TED5.EXE", "/LAUNCH", NULL);
+		}
+		else if (US_ParmPresent("windows"))
+		{
+			bioskey(0);
+		}
+		exit(1);
+	}
+
+	if (!NoWait)
+	{
+		movedata(finscreen, 7, 0xB800, 0, 4000);
+		gotoxy(1, 24);
+		if (US_ParmPresent("windows"))
+		{
+			bioskey(0);
+		}
+	}
+
+	exit(0);
+}
+
+//===========================================================================
+
+/*
+==================
+=
+= TEDDeath
+=
+==================
+*/
+
+void TEDDeath(void)
+{
+	ShutdownId();
+	execlp("TED5.EXE", "TED5.EXE", "/LAUNCH", NULL);
+	// BUG: should call exit(1); here in case starting TED5 fails
+}
+
+//===========================================================================
+
+/*
+==================
+=
+= CheckMemory
+=
+==================
+*/
+
+void CheckMemory(void)
+{
+	Uint16 finscreen;
+
+	if (mminfo.nearheap+mminfo.farheap+mminfo.EMSmem+mminfo.XMSmem >= MINMEMORY)
+		return;
+
+	CA_CacheGrChunk (OUTOFMEM);
+	finscreen = (Uint16)grsegs[OUTOFMEM];
+	ShutdownId();
+	movedata (finscreen,7,0xb800,0,4000);
+	gotoxy (1,24);
+	exit(1);
+}
+
+//===========================================================================
+
+/*
+=====================
+=
+= DemoLoop
+=
+=====================
+*/
+
+void DemoLoop(void)
+{
+	static char *ParmStrings[] = {"easy", "normal", "hard", ""};
+
+	register Sint16 i, state;
+	Sint16 level;
+
+//
+// check for launch from ted
+//
+	if (tedlevel)
+	{
+		NewGame();
+		CA_LoadAllSounds();
+		gamestate.mapon = tedlevelnum;
+		restartgame = gd_Normal;
+		for (i = 1;i < _argc;i++)
+		{
+			if ( (level = US_CheckParm(_argv[i],ParmStrings)) == -1)
+				continue;
+
+			restartgame = level+gd_Easy;
+			break;
+		}
+		GameLoop();
+		TEDDeath();
+	}
+
+//
+// demo loop
+//
+	state = 0;
+	playstate = ex_stillplaying;
+	while (1)
+	{
+		switch (state++)
+		{
+		case 0:
+#if GRMODE == CGAGR
+			ShowTitle();
+#else
+			if (nopan)
+			{
+				ShowTitle();
+			}
+			else
+			{
+				Terminator();
+			}
+#endif
+			break;
+
+		case 1:
+			RunDemo(0);
+			break;
+
+		case 2:
+#if GRMODE == CGAGR
+			ShowCredits();
+#else
+			StarWars();
+#endif
+			break;
+
+		case 3:
+			RunDemo(1);
+			break;
+
+		case 4:
+			ShowHighScores();
+			break;
+
+		case 5:
+			RunDemo(2);
+			break;
+
+		case 6:
+			state = 0;
+			RunDemo(3);
+			break;
+		}
+
+		while (playstate == ex_resetgame || playstate == ex_loadedgame)
+		{
+			GameLoop();
+			ShowHighScores();
+			if (playstate == ex_resetgame || playstate == ex_loadedgame)
+			{
+				continue;	// don't show title screen, go directly to GameLoop();
+			}
+			ShowTitle();
+			///////////////
+			// this is completely useless:
+			if (playstate == ex_resetgame || playstate == ex_loadedgame)
+			{
+				continue;
+			}
+			///////////////
+		}
+	}
+}
+
+//===========================================================================
+
+#if (GRMODE == EGAGR) && !(defined KEEN6)
+/*
+=====================
+=
+= CheckCutFile
+=
+=====================
+*/
+
+#define FILE_GR1 GREXT"1."EXTENSION
+#define FILE_GR2 GREXT"2."EXTENSION
+#define FILE_GRAPH GREXT"GRAPH."EXTENSION
+
+static void CheckCutFile(void)
+{
+	register Sint16 ohandle, ihandle;
+	Sint16 handle;
+	Sint32 size;
+	void far *buffer;
+
+	if ( (handle = open(FILE_GRAPH, O_BINARY|O_RDONLY)) != -1)
+	{
+		close(handle);
+		return;
+	}
+	puts("Combining "FILE_GR1" and "FILE_GR2" into "FILE_GRAPH"...");
+	if (rename(FILE_GR1, FILE_GRAPH) == -1)
+	{
+		puts("Can't rename "FILE_GR1"!");
+		exit(1);
+	}
+	if ( (ohandle = open(FILE_GRAPH, O_BINARY|O_APPEND|O_WRONLY)) == -1)
+	{
+		puts("Can't open "FILE_GRAPH"!");
+		exit(1);
+	}
+	lseek(ohandle, 0, SEEK_END);
+	if ( (ihandle = open(FILE_GR2, O_BINARY|O_RDONLY)) == -1)
+	{
+		puts("Can't find "FILE_GR2"!");
+		exit(1);
+	}
+	size = filelength(ihandle);
+	buffer = farmalloc(32000);
+	while (size)
+	{
+		if (size > 32000)
+		{
+			CA_FarRead(ihandle, buffer, 32000);
+			CA_FarWrite(ohandle, buffer, 32000);
+			size -= 32000;
+		}
+		else
+		{
+			CA_FarRead(ihandle, buffer, size);
+			CA_FarWrite(ohandle, buffer, size);
+			size = 0;
+		}
+	}
+	farfree(buffer);
+	close(ohandle);
+	close(ihandle);
+	unlink(FILE_GR2);
+}
+#endif
+
+//===========================================================================
+
+
+/*
+==========================
+=
+= main
+=
+==========================
+*/
+
+void main(void)
+{
+#if (GRMODE == EGAGR) && !(defined KEEN6)
+	CheckCutFile();
+#endif
+
+	if (US_ParmPresent("DEMO"))
+		storedemo = true;
+
+	if (US_ParmPresent("JOYPAD"))
+		joypad = true;	// Note: the joypad variable is never used
+	
+	InitGame();
+	CheckMemory();
+	if (NoWait || tedlevel)
+		debugok = true;
+
+	DemoLoop();
+	Quit("Demo loop exited???");
+}
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/CK_PLAY.C b/16/keen456/KEEN4-6/CK_PLAY.C
new file mode 100755
index 00000000..0e081405
--- /dev/null
+++ b/16/keen456/KEEN4-6/CK_PLAY.C
@@ -0,0 +1,2422 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+#include "CK_DEF.H"
+
+/*
+=============================================================================
+
+						 GLOBAL VARIABLES
+
+=============================================================================
+*/
+
+ScanCode firescan = sc_Space;
+
+boolean singlestep, jumpcheat, godmode, keenkilled;
+
+exittype playstate;
+gametype gamestate;
+
+objtype *new, *check, *player, *scoreobj;
+
+Uint16 originxtilemax;
+Uint16 originytilemax;
+
+ControlInfo c;
+boolean button2, button3;	// never used
+
+objtype dummyobj;
+
+Sint16 invincible;
+
+boolean oldshooting, showscorebox, joypad;
+
+Sint16 groundslam;
+
+boolean debugok;
+boolean jumpbutton, jumpheld, pogobutton, pogoheld, firebutton, fireheld, upheld;
+
+
+/*
+=============================================================================
+
+						 LOCAL VARIABLES
+
+=============================================================================
+*/
+
+objtype *obj;
+
+Uint16 centerlevel;
+
+Uint16 objectcount;
+objtype objarray[MAXACTORS];
+objtype *lastobj;
+objtype *objfreelist;
+
+Sint16 inactivateleft;
+Sint16 inactivateright;
+Sint16 inactivatetop;
+Sint16 inactivatebottom;
+
+#ifdef KEEN6Ev15
+Uint16 __dummy__;	// never used, but must be present to recreate the original EXE
+#endif
+
+Uint16 extravbls;
+
+Uint16 windowofs;
+Sint16 vislines;
+boolean scrollup;
+
+Sint16 oldfirecount;
+
+//===========================================================================
+
+/*
+==================
+=
+= CountObjects
+=
+==================
+*/
+
+void CountObjects(void)
+{
+	Uint16 activeobjects, inactiveobjects;
+	objtype *ob;
+
+	activeobjects = inactiveobjects = 0;
+	for (ob=player; ob; ob=ob->next)
+	{
+		if (ob->active)
+		{
+			activeobjects++;
+		}
+		else
+		{
+			inactiveobjects++;
+		}
+	}
+	VW_FixRefreshBuffer();
+	US_CenterWindow(18, 4);
+	PrintY += 7;
+	US_Print("Active Objects :");
+	US_PrintUnsigned(activeobjects);
+	US_Print("\nInactive Objects:");
+	US_PrintUnsigned(inactiveobjects);
+	VW_UpdateScreen();
+	IN_Ack();
+}
+
+/*
+==================
+=
+= DebugMemory
+=
+==================
+*/
+
+void DebugMemory(void)
+{
+	VW_FixRefreshBuffer();
+	US_CenterWindow(16, 7);
+	US_CPrint("Memory Usage");
+	US_CPrint("------------");
+	US_Print("Total     :");
+	US_PrintUnsigned((mminfo.mainmem+mminfo.EMSmem+mminfo.XMSmem)/1024);
+	US_Print("k\nFree      :");
+	US_PrintUnsigned(MM_UnusedMemory()/1024);
+	US_Print("k\nWith purge:");
+	US_PrintUnsigned(MM_TotalFree()/1024);
+	US_Print("k\n");
+	VW_UpdateScreen();
+	IN_Ack();
+#if GRMODE != CGAGR
+	MM_ShowMemory();
+#endif
+}
+
+/*
+===================
+=
+= TestSprites
+=
+===================
+*/
+
+void TestSprites(void)
+{
+	Uint16 infox, infoy;
+	Sint16 chunk, oldchunk;
+	Sint16 shift;
+	Uint16 infobottom, drawx;
+	spritetabletype far *info;
+	Uint8 _seg *block;
+	Uint16 size;
+	Uint16 scan;
+	Uint32 totalsize;
+
+	VW_FixRefreshBuffer();
+	US_CenterWindow(30, 17);
+	totalsize = 0;
+	US_CPrint("Sprite Test");
+	US_CPrint("-----------");
+	infoy = PrintY;
+	infox = (PrintX + 56) & ~7;
+	drawx = infox + 40;
+	US_Print("Chunk:\nWidth:\nHeight:\nOrgx:\nOrgy:\nXl:\nYl:\nXh:\nYh:\nShifts:\nMem:\n");
+	infobottom = PrintY;
+	chunk = STARTSPRITES;
+	shift = 0;
+	while (1)
+	{
+		if (chunk >= STARTSPRITES+NUMSPRITES)
+		{
+			chunk = STARTSPRITES+NUMSPRITES-1;
+		}
+		else if (chunk < STARTSPRITES)
+		{
+			chunk = STARTSPRITES;
+		}
+		info = &spritetable[chunk-STARTSPRITES];
+		block = grsegs[chunk];
+		VWB_Bar(infox, infoy, 40, infobottom-infoy, WHITE);
+		PrintX = infox;
+		PrintY = infoy;
+		US_PrintUnsigned(chunk);
+		US_Print("\n");
+		PrintX = infox;
+		US_PrintUnsigned(info->width);
+		US_Print("\n");
+		PrintX = infox;
+		US_PrintUnsigned(info->height);
+		US_Print("\n");
+		PrintX = infox;
+		US_PrintSigned(info->orgx);
+		US_Print("\n");
+		PrintX = infox;
+		US_PrintSigned(info->orgy);
+		US_Print("\n");
+		PrintX = infox;
+		US_PrintSigned(info->xl);
+		US_Print("\n");
+		PrintX = infox;
+		US_PrintSigned(info->yl);
+		US_Print("\n");
+		PrintX = infox;
+		US_PrintSigned(info->xh);
+		US_Print("\n");
+		PrintX = infox;
+		US_PrintSigned(info->yh);
+		US_Print("\n");
+		PrintX = infox;
+		US_PrintSigned(info->shifts);
+		US_Print("\n");
+		PrintX = infox;
+		if (!block)
+		{
+			US_Print("-----");
+		}
+		else
+		{
+			size = ((spritetype far *)block)->sourceoffset[3] + ((spritetype far *)block)->planesize[3]*5;
+			size = (size + 15) & ~15;	//round up to multiples of 16
+			totalsize += size;	//useless: the value stored in 'totalsize' is never used
+			US_PrintUnsigned(size);
+			US_Print("=");
+		}
+		oldchunk = chunk;
+		do
+		{
+			VWB_Bar(drawx, infoy, 110, infobottom-infoy, WHITE);
+			if (block)
+			{
+				PrintX = drawx;
+				PrintY = infoy;
+				US_Print("Shift:");
+				US_PrintUnsigned(shift);
+				US_Print("\n");
+				VWB_DrawSprite(drawx + 2*shift + 16, PrintY, chunk);
+			}
+			VW_UpdateScreen();
+			scan = IN_WaitForKey();
+			switch (scan)
+			{
+			case sc_UpArrow:
+				chunk++;
+				break;
+			case sc_DownArrow:
+				chunk--;
+				break;
+			case sc_PgUp:
+				chunk += 10;
+				if (chunk >= STARTSPRITES+NUMSPRITES)
+				{
+					chunk = STARTSPRITES+NUMSPRITES-1;
+				}
+				break;
+			case sc_PgDn:
+				chunk -= 10;
+				if (chunk < STARTSPRITES)
+				{
+					chunk = STARTSPRITES;
+				}
+				break;
+			case sc_LeftArrow:
+				if (--shift == -1)
+				{
+					shift = 3;
+				}
+				break;
+			case sc_RightArrow:
+				if (++shift == 4)
+				{
+					shift = 0;
+				}
+				break;
+			case sc_Escape:
+				return;
+			}
+
+		} while (chunk == oldchunk);
+
+	}
+}
+
+/*
+===================
+=
+= PicturePause
+=
+===================
+*/
+
+void PicturePause(void)
+{
+	Uint16 source;
+	Sint16 y;
+
+//
+// wait for a key press, abort if it's not Enter
+//
+	IN_ClearKeysDown();
+	while (!LastScan);
+	if (LastScan != sc_Enter)
+	{
+		IN_ClearKeysDown();
+		return;
+	}
+
+	SD_PlaySound(SND_JUMP);
+	SD_WaitSoundDone();
+
+//
+// rearrange onscreen image into base EGA layout, so that it
+// can be grabbed correctly by an external screenshot tool
+//
+	source = displayofs + panadjust;
+
+	VW_ColorBorder(15);	// white (can't use WHITE as parameter, since that's defined as 3 for CGA and this must use 15)
+	VW_SetLineWidth(40);
+	VW_SetScreen(0, 0);
+
+	if (source < 0x10000l-200*64)
+	{
+	//
+	// copy top line first
+	//
+		for (y=0; y<200; y++)
+		{
+			VW_ScreenToScreen(source+y*64, y*40, 40, 1);
+		}
+	}
+	else
+	{
+	//
+	// copy bottom line first
+	//
+		for (y=199; y>=0; y--)
+		{
+			VW_ScreenToScreen(source+y*64, y*40, 40, 1);
+		}
+	}
+
+//
+// shut down input manager so that screenshot tool can see input again
+//
+	IN_Shutdown();
+
+	SD_PlaySound(SND_EXTRAKEEN);
+	SD_WaitSoundDone();
+
+//
+// shut down the remaining ID managers, except VW (stay in graphics mode!)
+//
+	US_Shutdown();
+	SD_Shutdown();
+	IN_Shutdown();
+	RF_Shutdown();
+	CA_Shutdown();
+	MM_Shutdown();
+
+//
+// wait until user hits Escape
+//
+	while (((bioskey(0) >> 8) & 0xFF) != sc_Escape);
+
+//
+// back to text mode and exit to DOS
+//
+	VW_Shutdown();
+	exit(0);
+}
+
+/*
+===================
+=
+= MaskOnTile
+=
+===================
+*/
+
+void MaskOnTile(Uint16 dest, Uint16 source)
+{
+	Sint16 i;
+	Uint16 _seg *sourceseg;
+	Uint16 _seg *destseg;
+	Uint16 sourceval, maskindex, sourcemask;
+
+	sourceseg = (grsegs+STARTTILE16M)[source];
+	destseg = (grsegs+STARTTILE16M)[dest];
+	for (i=0; i<64; i++)
+	{
+		maskindex = i & 15;
+#ifdef KEEN6Ev15
+		sourceval = sourceseg[16+i];
+#else
+		sourceval = (sourceseg+16)[i];
+#endif
+		sourcemask = sourceseg[maskindex];
+		destseg[maskindex] &= sourcemask;
+		destseg[16+i] &= sourcemask;
+		destseg[16+i] |= sourceval;
+	}
+}
+
+/*
+===================
+=
+= WallDebug
+=
+===================
+*/
+
+void WallDebug(void)
+{
+	Sint16 i, val;
+
+	VW_FixRefreshBuffer();
+	US_CenterWindow(24, 3);
+	US_PrintCentered("WORKING");
+	VW_UpdateScreen();
+	for (i=STARTTILE16M+108; i<STARTTILE16M+124; i++)
+	{
+		CA_CacheGrChunk(i);
+	}
+	for (i=0; i<NUMTILE16M; i++)
+	{
+		if (!grsegs[STARTTILE16M+i])
+		{
+			continue;
+		}
+		val = tinf[i+NORTHWALL] & 7;
+		if (val)
+		{
+			MaskOnTile(i, val+107);
+		}
+		val = tinf[i+SOUTHWALL] & 7;
+		if (val)
+		{
+			MaskOnTile(i, val+115);
+		}
+		val = tinf[i+EASTWALL] & 7;
+		if (val > 1)
+		{
+			strcpy(str, "WallDebug: East wall other than 1:");
+			itoa(i, str2, 10);
+			strcat(str, str2);
+			Quit(str);
+		}
+		if (val)
+		{
+			MaskOnTile(i, val+114);	//Note: val is always 1 here, so you could use 115 as 2nd arg
+		}
+		val = tinf[i+WESTWALL] & 7;
+		if (val > 1)
+		{
+			strcpy(str, "WallDebug: West wall other than 1:");
+			itoa(i, str2, 10);
+			strcat(str, str2);
+			Quit(str);
+		}
+		if (val)
+		{
+			MaskOnTile(i, val+122);	//Note: val is always 1 here, so you could use 123 as 2nd arg
+		}
+	}
+}
+
+
+//===========================================================================
+
+/*
+================
+=
+= DebugKeys
+=
+================
+*/
+
+boolean DebugKeys(void)
+{
+	Sint16 level, i, esc;
+
+	if (Keyboard[sc_B] && ingame)		// B = border color
+	{
+		VW_FixRefreshBuffer();
+		US_CenterWindow(24, 3);
+		PrintY += 6;
+		US_Print(" Border color (0-15):");
+		VW_UpdateScreen();
+		esc = !US_LineInput(px, py, str, NULL, true, 2, 0);
+		if (!esc)
+		{
+			level = atoi(str);
+			if (level >= 0 && level <= 15)
+			{
+				VW_ColorBorder(level);
+			}
+		}
+		return true;
+	}
+
+	if (Keyboard[sc_C] && ingame)		// C = count objects
+	{
+		CountObjects();
+		return true;
+	}
+
+	if (Keyboard[sc_D] && ingame)		// D = start / end demo record
+	{
+		if (DemoMode == demo_Off)
+		{
+			StartDemoRecord();
+		}
+		else if (DemoMode == demo_Record)
+		{
+			EndDemoRecord();
+			playstate = ex_completed;
+		}
+		return true;
+	}
+
+	if (Keyboard[sc_E] && ingame)		// E = quit level
+	{
+		if (tedlevel)
+		{
+			TEDDeath();
+		}
+		playstate = ex_completed;
+		//BUG? there is no return in this branch (should return false)
+	}
+
+	if (Keyboard[sc_G] && ingame)		// G = god mode
+	{
+		VW_FixRefreshBuffer();
+		US_CenterWindow(12, 2);
+		if (godmode)
+		{
+			US_PrintCentered("God mode OFF");
+		}
+		else
+		{
+			US_PrintCentered("God mode ON");
+		}
+		VW_UpdateScreen();
+		IN_Ack();
+		godmode ^= true;
+		return true;
+	}
+	else if (Keyboard[sc_I])			// I = item cheat
+	{
+		VW_FixRefreshBuffer();
+		US_CenterWindow(12, 3);
+		US_PrintCentered("Free items!");
+		for (i=0; i<4; i++)
+		{
+			gamestate.keys[i] = 99;
+		}
+		gamestate.ammo = 99;
+#if defined KEEN4
+		gamestate.wetsuit = true;
+#elif defined KEEN5
+		gamestate.keycard = true;
+#elif defined KEEN6
+		gamestate.passcardstate=gamestate.hookstate=gamestate.sandwichstate = 1;
+#endif
+		VW_UpdateScreen();
+		IN_Ack();
+		GivePoints(3000);
+		return true;
+	}
+	else if (Keyboard[sc_J])			// J = jump cheat
+	{
+		jumpcheat ^= true;
+		VW_FixRefreshBuffer();
+		US_CenterWindow(18, 3);
+		if (jumpcheat)
+		{
+			US_PrintCentered("Jump cheat ON");
+		}
+		else
+		{
+			US_PrintCentered("Jump cheat OFF");
+		}
+		VW_UpdateScreen();
+		IN_Ack();
+		return true;
+	}
+	else if (Keyboard[sc_M])			// M = memory info
+	{
+		DebugMemory();
+		return true;
+	}
+	else if (Keyboard[sc_N])			// N = no clip
+	{
+		VW_FixRefreshBuffer();
+		US_CenterWindow(18, 3);
+		if (player->needtoclip)
+		{
+			US_PrintCentered("No clipping ON");
+			player->needtoclip = cl_noclip;
+		}
+		else
+		{
+			US_PrintCentered("No clipping OFF");
+			player->needtoclip = cl_midclip;
+		}
+		VW_UpdateScreen();
+		IN_Ack();
+		return true;
+	}
+	else if (Keyboard[sc_P])			// P = pause with no screen disruptioon
+	{
+		IN_ClearKeysDown();
+		PicturePause();
+		return true;
+	}
+	else if (Keyboard[sc_S] && ingame)	// S = slow motion
+	{
+		singlestep ^= true;
+		VW_FixRefreshBuffer();
+		US_CenterWindow(18, 3);
+		if (singlestep)
+		{
+			US_PrintCentered("Slow motion ON");
+		}
+		else
+		{
+			US_PrintCentered("Slow motion OFF");
+		}
+		VW_UpdateScreen();
+		IN_Ack();
+		return true;
+	}
+	else if (Keyboard[sc_T])			// T = sprite test
+	{
+		TestSprites();
+		return true;
+	}
+	else if (Keyboard[sc_V])			// V = extra VBLs
+	{
+		VW_FixRefreshBuffer();
+		US_CenterWindow(30, 3);
+		PrintY += 6;
+		US_Print("  Add how many extra VBLs(0-8):");
+		VW_UpdateScreen();
+		esc = !US_LineInput(px, py, str, NULL, true, 2, 0);
+		if (!esc)
+		{
+			level = atoi(str);
+			if (level >= 0 && level <= 8)
+			{
+				extravbls = level;
+			}
+		}
+		return true;
+	}
+	else if (Keyboard[sc_W] && ingame)	// W = warp to level
+	{
+		VW_FixRefreshBuffer();
+		US_CenterWindow(26, 3);
+		PrintY += 6;
+		US_Print("  Warp to which level(1-18):");
+		VW_UpdateScreen();
+		esc = !US_LineInput(px, py, str, NULL, true, 2, 0);
+		if (!esc)
+		{
+			level = atoi(str);
+			if (level > 0 && level <= 18)
+			{
+				gamestate.mapon = level;
+				playstate = ex_warped;
+			}
+		}
+		return true;
+	}
+	else if (Keyboard[sc_Y])			// Y = wall debug
+	{
+		WallDebug();
+		return true;
+	}
+	else if (Keyboard[sc_Z])			// Z = game over
+	{
+		gamestate.lives = 0;
+		KillKeen();
+		return false;
+	}
+	return false;
+}
+
+//===========================================================================
+
+/*
+================
+=
+= UserCheat
+=
+================
+*/
+
+void UserCheat(void)
+{
+	Sint16 i;
+
+	for (i=sc_A; i<=sc_Z; i++)	//Note: this does NOT check the keys in alphabetical order!
+	{
+		if (i != sc_B && i != sc_A && i != sc_T && Keyboard[i])
+		{
+			return;
+		}
+	}
+	US_CenterWindow(20, 7);
+	PrintY += 2;
+	US_CPrint(
+		"Cheat Option!\n"
+		"\n"
+		"You just got all\n"
+		"the keys, 99 shots,\n"
+		"and an extra keen!");
+	VW_UpdateScreen();
+	IN_Ack();
+	RF_ForceRefresh();
+	gamestate.ammo = 99;
+	gamestate.lives++;
+#ifdef KEEN5
+	gamestate.keycard = true;
+#endif
+	gamestate.keys[0] = gamestate.keys[1] = gamestate.keys[2] = gamestate.keys[3] = 1;
+}
+
+//===========================================================================
+
+/*
+=====================
+=
+= CheckKeys
+=
+=====================
+*/
+
+void CheckKeys(void)
+{
+	if (screenfaded)			// don't do anything with a faded screen
+	{
+		return;
+	}
+
+//
+// Enter for status screen
+//
+	if (Keyboard[sc_Enter] || (GravisGamepad && GravisAction[ga_Status]))
+	{
+		StatusWindow();
+		IN_ClearKeysDown();
+		RF_ForceRefresh();
+		lasttimecount = TimeCount;	// BUG: should be the other way around
+	}
+
+//
+// pause key wierdness can't be checked as a scan code
+//
+	if (Paused)
+	{
+		SD_MusicOff();
+		VW_FixRefreshBuffer();
+		US_CenterWindow(8, 3);
+		US_PrintCentered("PAUSED");
+		VW_UpdateScreen();
+		IN_Ack();
+		RF_ForceRefresh();
+		Paused = false;
+		SD_MusicOn();
+	}
+
+#ifndef KEEN6
+//
+// F1 to enter help screens
+//
+	if (LastScan == sc_F1)
+	{
+		StopMusic();
+		HelpScreens();
+		StartMusic(gamestate.mapon);
+		if (showscorebox)
+		{
+			scoreobj->temp2 = -1;
+			scoreobj->temp1 = -1;
+			scoreobj->temp3 = -1;
+			scoreobj->temp4 = -1;
+		}
+		RF_ForceRefresh();
+	}
+#endif
+
+	if (!storedemo)
+	{
+//
+// F2-F7/ESC to enter control panel
+//
+		if (LastScan >= sc_F2 && LastScan <= sc_F7 || LastScan == sc_Escape)
+		{
+			VW_FixRefreshBuffer();
+			StopMusic();
+			US_ControlPanel();
+			RF_FixOfs();
+			StartMusic(gamestate.mapon);
+			if (!showscorebox && scoreobj->sprite)
+			{
+				RF_RemoveSprite(&scoreobj->sprite);
+			}
+			if (showscorebox)
+			{
+				scoreobj->temp2 = -1;
+				scoreobj->temp1 = -1;
+				scoreobj->temp3 = -1;
+				scoreobj->temp4 = -1;
+			}
+			IN_ClearKeysDown();
+			if (restartgame)
+			{
+				playstate = ex_resetgame;
+			}
+			else if (!loadedgame)
+			{
+				RF_ForceRefresh();
+			}
+			if (abortgame)
+			{
+				abortgame = false;
+				playstate = ex_abortgame;
+			}
+			if (loadedgame)
+			{
+				playstate = ex_loadedgame;
+			}
+			lasttimecount = TimeCount;	// BUG: should be the other way around
+		}
+
+//
+// F9 boss key
+//
+		if (LastScan == sc_F9)
+		{
+			VW_Shutdown();
+			SD_MusicOff();
+			cputs("C:>");
+			IN_ClearKeysDown();
+			while (LastScan != sc_Escape);
+			VW_SetScreenMode(GRMODE);
+			VW_ColorBorder(bordercolor);
+			RF_ForceRefresh();
+			IN_ClearKeysDown();
+			lasttimecount = TimeCount;	// BUG: should be the other way around
+			SD_MusicOn();
+		}
+	}
+
+//
+// B-A-T cheat code
+//
+	if (Keyboard[sc_B] && Keyboard[sc_A] && Keyboard[sc_T])
+	{
+		UserCheat();
+	}
+
+//
+// F10-? debug keys
+//
+	if (debugok && Keyboard[sc_F10])
+	{
+		if (DebugKeys())
+		{
+			RF_ForceRefresh();
+			lasttimecount = TimeCount;	// BUG: should be the other way around
+		}
+	}
+
+//
+// Ctrl-S toggles sound (only in storedemo mode)
+//
+	if (storedemo && Keyboard[sc_Control] && LastScan == sc_S)
+	{
+		if (SoundMode != sdm_Off)
+		{
+			SD_SetSoundMode(sdm_Off);
+			SD_SetMusicMode(smm_Off);
+		}
+		else
+		{
+			if (AdLibPresent)
+			{
+				SD_SetSoundMode(sdm_AdLib);
+				QuietFX = false;
+				SD_SetMusicMode(smm_AdLib);
+			}
+			else
+			{
+				SD_SetSoundMode(sdm_PC);
+				SD_SetMusicMode(smm_Off);
+			}
+			CA_LoadAllSounds();
+		}
+	}
+
+//
+// Ctrl-Q quick quit
+//
+	if (Keyboard[sc_Control] && LastScan == sc_Q)
+	{
+		IN_ClearKeysDown();
+		Quit(NULL);
+	}
+}
+
+//===========================================================================
+
+/*
+==================
+=
+= PrintNumbers
+=
+==================
+*/
+
+void PrintNumbers(Sint16 x, Sint16 y, Sint16 maxlen, Sint16 basetile, Sint32 number)
+{
+	register Sint16 i;
+	Sint16 len;
+	char buffer[20];
+
+	ltoa(number, buffer, 10);
+	len = strlen(buffer);
+	i = maxlen;
+	while (i>len)
+	{
+		VWB_DrawTile8(x, y, basetile);
+		i--;
+		x += 8;
+	}
+	while (i>0)
+	{
+		VWB_DrawTile8(x, y, basetile+buffer[len-i]+(1-'0'));
+		i--;
+		x += 8;
+	}
+}
+
+/*
+==================
+=
+= DrawStatusWindow
+=
+==================
+*/
+
+#if GRMODE == CGAGR
+
+#define BACKCOLOR WHITE
+#define TEXTBACK BLACK
+#define NUMBERBACK BLACK
+
+#else
+
+#define BACKCOLOR LIGHTGRAY
+#define TEXTBACK WHITE
+#define NUMBERBACK BLACK
+
+#endif
+
+void DrawStatusWindow(void)
+{
+	Sint16 off, x, y, w, h, i;
+	Uint16 width, height;
+
+	x = 64;
+	y = 16;
+	w = 184;
+	h = 144;
+	VWB_DrawTile8(x, y, 54);
+	VWB_DrawTile8(x, y+h, 60);
+	for (i=x+8; i<=x+w-8; i+=8)
+	{
+		VWB_DrawTile8(i, y, 55);
+		VWB_DrawTile8(i, y+h, 61);
+	}
+	VWB_DrawTile8(i, y, 56);
+	VWB_DrawTile8(i, y+h, 62);
+	for (i=y+8; i<=y+h-8; i+=8)
+	{
+		VWB_DrawTile8(x, i, 57);
+		VWB_DrawTile8(x+w, i, 59);
+	}
+	VWB_Bar(72, 24, 176, 136, BACKCOLOR);
+
+	PrintY = 28;
+	WindowX = 80;
+	WindowW = 160;
+	US_CPrint("LOCATION");
+	VWB_Bar(79, 38, 162, 20, TEXTBACK);
+#ifdef KEEN5
+	if (mapon == 0 && player->y > 100*TILEGLOBAL)
+		_fstrcpy(str, levelnames[13]);
+	else
+		_fstrcpy(str, levelnames[gamestate.mapon]);
+#else
+	_fstrcpy(str, levelnames[gamestate.mapon]);
+#endif
+	SizeText(str, &width, &height);
+	PrintY = (20-height)/2+40-2;
+	US_CPrint(str);
+
+	PrintY = 61;
+	WindowX = 80;
+	WindowW = 64;
+	US_CPrint("SCORE");
+	VWB_Bar(79, 71, 66, 10, NUMBERBACK);
+	PrintNumbers(80, 72, 8, 41, gamestate.score);
+
+	PrintY = 61;
+	WindowX = 176;
+	WindowW = 64;
+	US_CPrint("EXTRA");
+	VWB_Bar(175, 71, 66, 10, NUMBERBACK);
+	PrintNumbers(176, 72, 8, 41, gamestate.nextextra);
+
+#if defined KEEN4
+	PrintY = 85;
+	WindowX = 80;
+	WindowW = 64;
+	US_CPrint("RESCUED");
+	VWB_Bar(79, 95, 66, 10, NUMBERBACK);
+	for (i = 0; i < gamestate.rescued; i++, off+=8)
+	{
+		VWB_DrawTile8(i*8 + 80, 96, 40);
+	}
+#elif defined KEEN5
+	PrintY = 92;
+	PrintX = 80;
+	US_Print("KEYCARD");
+	VWB_Bar(135, 91, 10, 10, NUMBERBACK);
+	if (gamestate.keycard)
+	{
+		VWB_DrawTile8(136, 92, 40);
+	}
+#endif
+
+	PrintY = 85;
+	WindowX = 176;
+	WindowW = 64;
+	US_CPrint("LEVEL");
+	VWB_Bar(175, 95, 66, 10, TEXTBACK);
+	PrintY = 96;
+	WindowX = 176;
+	WindowW = 64;
+	switch (gamestate.difficulty)
+	{
+	case gd_Easy:
+		US_CPrint("Easy");
+		break;
+	case gd_Normal:
+		US_CPrint("Normal");
+		break;
+	case gd_Hard:
+		US_CPrint("Hard");
+		break;
+	}
+
+#ifdef KEEN6
+	PrintX = 80;
+	PrintY = 96;
+	US_Print("ITEMS");
+	VWB_Bar(127, 95, 26, 10, NUMBERBACK);
+	if (gamestate.sandwichstate == 1)
+	{
+		VWB_DrawTile8(128, 96, 2);
+	}
+	else
+	{
+		VWB_DrawTile8(128, 96, 1);
+	}
+	if (gamestate.hookstate == 1)
+	{
+		VWB_DrawTile8(136, 96, 4);
+	}
+	else
+	{
+		VWB_DrawTile8(136, 96, 3);
+	}
+	if (gamestate.passcardstate == 1)
+	{
+		VWB_DrawTile8(144, 96, 6);
+	}
+	else
+	{
+		VWB_DrawTile8(144, 96, 5);
+	}
+#endif
+
+	PrintX = 80;
+	PrintY = 112;
+	US_Print("KEYS");
+	VWB_Bar(119, 111, 34, 10, NUMBERBACK);
+	for (i = 0; i < 4; i++)
+	{
+		if (gamestate.keys[i])
+		{
+			VWB_DrawTile8(i*8+120, 112, 36+i);
+		}
+	}
+
+	PrintX = 176;
+	PrintY = 112;
+	US_Print("AMMO");
+	VWB_Bar(215, 111, 26, 10, NUMBERBACK);
+	PrintNumbers(216, 112, 3, 41, gamestate.ammo);
+
+	PrintX = 80;
+	PrintY = 128;
+	US_Print("KEENS");
+	VWB_Bar(127, 127, 18, 10, NUMBERBACK);
+	PrintNumbers(128, 128, 2, 41, gamestate.lives);
+
+	PrintX = 176;
+	PrintY = 128;
+	US_Print(DROPSNAME);
+	VWB_Bar(224, 127, 16, 10, NUMBERBACK);
+	PrintNumbers(224, 128, 2, 41, gamestate.drops);
+
+#ifdef KEEN4
+	VWB_Bar(79, 143, 66, 10, TEXTBACK);
+	PrintY = 144;
+	WindowX = 80;
+	WindowW = 64;
+	if (gamestate.wetsuit)
+	{
+		US_CPrint("Wetsuit");
+	}
+	else
+	{
+		US_CPrint("???");
+	}
+#endif
+
+	// draw the tiles for "PRESS A KEY":
+	for (i = 0; i < 10; i++)
+	{
+		VWB_DrawTile8(i*8+STATUS_PRESSKEY_X, 140, i+72);
+		VWB_DrawTile8(i*8+STATUS_PRESSKEY_X, 148, i+82);
+	}
+}
+
+/*
+==================
+=
+= ScrollStatusWindow
+=
+==================
+*/
+
+void ScrollStatusWindow(void)
+{
+	Uint16 source, dest;
+	Sint16 height;
+
+	if (vislines > 152)
+	{
+		height = vislines - 152;
+		source = windowofs + panadjust + 8;
+		dest = bufferofs + panadjust + 8;
+		VW_ScreenToScreen(source, dest, 192/BYTEPIXELS, height);
+		VW_ClipDrawMPic((pansx+136)/BYTEPIXELS, -(16-height)+pansy, METALPOLEPICM);
+		source = windowofs + panadjust + 16*SCREENWIDTH + 8*CHARWIDTH;
+		dest = bufferofs + panadjust + height*SCREENWIDTH + 8;
+		height = 152;
+	}
+	else
+	{
+		source = windowofs + panadjust + (152-vislines)*SCREENWIDTH + 16*SCREENWIDTH + 8*CHARWIDTH;
+		dest = bufferofs + panadjust + 8;
+		height = vislines;
+	}
+	if (height > 0)
+	{
+		VW_ScreenToScreen(source, dest, 192/BYTEPIXELS, height);
+	}
+	if (scrollup)
+	{
+		height = 168-vislines;
+		source = masterofs + panadjust + vislines*SCREENWIDTH + 8;
+		dest = bufferofs + panadjust + vislines*SCREENWIDTH + 8;
+		VW_ScreenToScreen(source, dest, 192/BYTEPIXELS, height);
+		height = vislines;
+		source = windowofs + panadjust + 8 - 24/BYTEPIXELS;
+		dest = bufferofs + panadjust + 8 - 24/BYTEPIXELS;
+		if (height > 0)
+			VW_ScreenToScreen(source, dest, 24/BYTEPIXELS, height);
+	}
+	else
+	{
+		height = vislines + -72;
+		if (height > 0)
+		{
+			source = windowofs + panadjust + 8 - 24/BYTEPIXELS;
+			dest = bufferofs + panadjust + 8 - 24/BYTEPIXELS;
+			if (height > 0)
+				VW_ScreenToScreen(source, dest, 24/BYTEPIXELS, height);
+		}
+	}
+	if (vislines >= 72)
+	{
+		VW_ClipDrawMPic((pansx+40)/BYTEPIXELS, vislines-168+pansy, CORDPICM);
+	}
+	VW_UpdateScreen();
+}
+
+/*
+==================
+=
+= StatusWindow
+=
+==================
+*/
+
+void StatusWindow(void)
+{
+#if GRMODE == CGAGR
+
+	if (Keyboard[sc_A] && Keyboard[sc_2])
+	{
+		US_CenterWindow(20, 2);
+		PrintY += 2;
+		US_Print("Debug keys active");
+		VW_UpdateScreen();
+		IN_Ack();
+		debugok = true;
+	}
+
+	WindowX = 0;
+	WindowW = 320;
+	WindowY = 0;
+	WindowH = 200;
+	DrawStatusWindow();
+	VW_UpdateScreen();
+	IN_ClearKeysDown();
+	IN_Ack();
+
+#else
+
+	Uint16 oldbufferofs;
+
+	WindowX = 0;
+	WindowW = 320;
+	WindowY = 0;
+	WindowH = 200;
+
+	if (Keyboard[sc_A] && Keyboard[sc_2])
+	{
+		US_CenterWindow(20, 2);
+		PrintY += 2;
+		US_Print("Debug keys active");
+		VW_UpdateScreen();
+		IN_Ack();
+		debugok = true;
+	}
+
+	RF_Refresh();
+	RFL_InitAnimList();
+	oldbufferofs = bufferofs;
+	bufferofs = windowofs = RF_FindFreeBuffer();
+	VW_ScreenToScreen(displayofs, displayofs, 44, 224);	// useless (source and dest offsets are identical)
+	VW_ScreenToScreen(displayofs, masterofs, 44, 224);
+	VW_ScreenToScreen(displayofs, bufferofs, 44, 168);
+	DrawStatusWindow();
+	bufferofs = oldbufferofs;
+	RF_Refresh();
+
+	SD_PlaySound(SND_SHOWSTATUS);
+	vislines = 16;
+	scrollup = false;
+	RF_SetRefreshHook(ScrollStatusWindow);
+
+	while (true)
+	{
+		RF_Refresh();
+		if (vislines == 168)
+			break;
+		vislines = vislines + tics*8;
+		if (vislines > 168)
+			vislines = 168;
+	}
+
+	RF_Refresh();
+	RF_SetRefreshHook(NULL);
+	IN_ClearKeysDown();
+	IN_Ack();
+
+	SD_PlaySound(SND_HIDESTATUS);
+	vislines -= 16;
+	scrollup = true;
+	RF_SetRefreshHook(ScrollStatusWindow);
+
+	while (true)
+	{
+		RF_Refresh();
+		if (vislines == 0)
+			break;
+		vislines = vislines - tics*8;
+		if (vislines < 0)
+			vislines = 0;
+	}
+
+	RF_SetRefreshHook(NULL);
+
+	scoreobj->x = 0;	//force scorebox to redraw?
+
+#endif
+}
+
+//===========================================================================
+
+/*
+==================
+=
+= CenterActor
+=
+==================
+*/
+
+void CenterActor(objtype *ob)
+{
+	Uint16 orgx, orgy;
+
+	centerlevel = 140;
+	if (ob->x < 152*PIXGLOBAL)
+	{
+		orgx = 0;
+	}
+	else
+	{
+		orgx = ob->x - 152*PIXGLOBAL;
+	}
+	if (mapon == 0)
+	{
+		if (ob->y < 80*PIXGLOBAL)
+		{
+			orgy = 0;
+		}
+		else
+		{
+			orgy = ob->y - 80*PIXGLOBAL;
+		}
+	}
+	else
+	{
+		if (ob->bottom < 140*PIXGLOBAL)
+		{
+			orgy = 0;
+		}
+		else
+		{
+			orgy = ob->bottom - 140*PIXGLOBAL;
+		}
+	}
+	if (!scorescreenkludge)
+	{
+		RF_NewPosition(orgx, orgy);
+	}
+
+//
+// update limits for onscreen and inactivate checks
+//
+	originxtilemax = (originxtile + PORTTILESWIDE) - 1;
+	originytilemax = (originytile + PORTTILESHIGH) - 1;
+	inactivateleft = originxtile - INACTIVATEDIST;
+	if (inactivateleft < 0)
+	{
+		inactivateleft = 0;
+	}
+	inactivateright = originxtilemax + INACTIVATEDIST;
+	if (inactivateright < 0)
+	{
+		inactivateright = 0;
+	}
+	inactivatetop = originytile - INACTIVATEDIST;
+	if (inactivatetop < 0)
+	{
+		inactivatetop = 0;
+	}
+	inactivatebottom = originytilemax + INACTIVATEDIST;
+	if (inactivatebottom < 0)
+	{
+		inactivatebottom = 0;
+	}
+}
+
+//===========================================================================
+
+/*
+==================
+=
+= WorldScrollScreen
+=
+= Scroll if Keen is nearing an edge
+=
+==================
+*/
+
+void WorldScrollScreen(objtype *ob)
+{
+	Sint16 xscroll, yscroll;
+
+	if (keenkilled)
+		return;
+
+	if (ob->left < originxglobal + 9*TILEGLOBAL)
+	{
+		xscroll = ob->left - (originxglobal + 9*TILEGLOBAL);
+	}
+	else if (ob->right > originxglobal + 12*TILEGLOBAL)
+	{
+		xscroll = ob->right + 16 - (originxglobal + 12*TILEGLOBAL);
+	}
+	else
+	{
+		xscroll = 0;
+	}
+
+	if (ob->top < originyglobal + 5*TILEGLOBAL)
+	{
+		yscroll = ob->top - (originyglobal + 5*TILEGLOBAL);
+	}
+	else if (ob->bottom > originyglobal + 7*TILEGLOBAL)
+	{
+		yscroll = ob->bottom - (originyglobal + 7*TILEGLOBAL);
+	}
+	else
+	{
+		yscroll = 0;
+	}
+
+	if (!xscroll && !yscroll)
+		return;
+
+//
+// don't scroll more than one tile per frame
+//
+	if (xscroll >= 0x100)
+	{
+		xscroll = 0xFF;
+	}
+	else if (xscroll <= -0x100)
+	{
+		xscroll = -0xFF;
+	}
+	if (yscroll >= 0x100)
+	{
+		yscroll = 0xFF;
+	}
+	else if (yscroll <= -0x100)
+	{
+		yscroll = -0xFF;
+	}
+
+	RF_Scroll(xscroll, yscroll);
+
+//
+// update limits for onscreen and inactivate checks
+//
+	originxtilemax = (originxtile + PORTTILESWIDE) - 1;
+	originytilemax = (originytile + PORTTILESHIGH) - 1;
+	inactivateleft = originxtile - INACTIVATEDIST;
+	if (inactivateleft < 0)
+	{
+		inactivateleft = 0;
+	}
+	inactivateright = originxtilemax + INACTIVATEDIST;
+	if (inactivateright < 0)
+	{
+		inactivateright = 0;
+	}
+	inactivatetop = originytile - INACTIVATEDIST;
+	if (inactivatetop < 0)
+	{
+		inactivatetop = 0;
+	}
+	inactivatebottom = originytilemax + INACTIVATEDIST;
+	if (inactivatebottom < 0)
+	{
+		inactivatebottom = 0;
+	}
+}
+
+//===========================================================================
+
+/*
+==================
+=
+= ScrollScreen
+=
+= Scroll if Keen is nearing an edge
+= Set playstate to ex_completes
+=
+==================
+*/
+
+void ScrollScreen(objtype *ob)
+{
+	Sint16 xscroll, yscroll, pix, speed;
+	Uint16 bottom;
+
+	if (keenkilled)
+		return;
+
+//
+// walked off edge of map?
+//
+	if (ob->left < originxmin || ob->right > originxmax + 320*PIXGLOBAL)
+	{
+		playstate = ex_completed;
+		return;
+	}
+
+//
+// fallen off bottom of world?
+//
+	if (ob->bottom > originymax + 13*TILEGLOBAL)
+	{
+		ob->y -= ob->bottom - (originymax + 13*TILEGLOBAL);
+		SD_PlaySound(SND_PLUMMET);
+		godmode = false;
+		KillKeen();
+		return;
+	}
+
+	xscroll=yscroll=0;
+
+	if (ob->x < originxglobal + 9*TILEGLOBAL)
+	{
+		xscroll = ob->x - (originxglobal + 9*TILEGLOBAL);
+	}
+	else if (ob->x > originxglobal + 12*TILEGLOBAL)
+	{
+		xscroll = ob->x - (originxglobal + 12*TILEGLOBAL);
+	}
+
+	if (ob->state == &s_keenlookup2)
+	{
+		if (centerlevel+tics > 167)
+		{
+			pix = 167-centerlevel;
+		}
+		else
+		{
+			pix = tics;
+		}
+		centerlevel += pix;
+		yscroll = CONVERT_PIXEL_TO_GLOBAL(-pix);
+	}
+	else if (ob->state == &s_keenlookdown3)
+	{
+		if (centerlevel-tics < 33)
+		{
+			pix = centerlevel + -33;
+		}
+		else
+		{
+			pix = tics;
+		}
+		centerlevel -= pix;
+		yscroll = CONVERT_PIXEL_TO_GLOBAL(pix);
+	}
+
+#ifdef KEEN6
+	if (groundslam)
+	{
+		static Sint16 shaketable[] = {0,
+			 -64,  -64,  -64,  64,  64,  64,
+			-200, -200, -200, 200, 200, 200,
+			-250, -250, -250, 250, 250, 250,
+			-250, -250, -250, 250, 250, 250
+		};
+		yscroll = yscroll + (bottom - (ob->bottom + shaketable[groundslam]));	// BUG: 'bottom' has not been initialized yet!
+	}
+	else
+#endif
+	if ( (ob->hitnorth || !ob->needtoclip || ob->state == &s_keenholdon))
+	{
+		if (  ob->state != &s_keenclimbup
+			&& ob->state != &s_keenclimbup2
+			&& ob->state != &s_keenclimbup3
+			&& ob->state != &s_keenclimbup4)
+		{
+			yscroll += ob->ymove;
+			bottom = originyglobal + yscroll + CONVERT_PIXEL_TO_GLOBAL(centerlevel);
+			if (ob->bottom == bottom)
+			{
+				// player didn't move, no additional scrolling
+			}
+			else
+			{
+				if (ob->bottom < bottom)
+				{
+					pix = bottom - ob->bottom;
+				}
+				else
+				{
+					pix = ob->bottom - bottom;
+				}
+				speed = CONVERT_PIXEL_TO_GLOBAL(pix) >> 7;
+				if (speed > 0x30)
+				{
+					speed = 0x30;
+				}
+				speed *= tics;
+				if (speed < 0x10)
+				{
+					if (pix < 0x10)
+					{
+						speed = pix;
+					}
+					else
+					{
+						speed = 0x10;
+					}
+				}
+				if (ob->bottom < bottom)
+				{
+					yscroll -= speed;
+				}
+				else
+				{
+					yscroll += speed;
+				}
+			}
+		}
+	}
+	else
+	{
+		centerlevel = 140;
+	}
+
+	pix = (ob->bottom-32*PIXGLOBAL)-(originyglobal+yscroll);
+	if (pix < 0)
+	{
+		yscroll += pix;
+	}
+	pix = (ob->bottom+32*PIXGLOBAL)-(originyglobal+yscroll+200*PIXGLOBAL);
+	if (pix > 0)
+	{
+		yscroll += pix;
+	}
+
+	if (xscroll == 0 && yscroll == 0)
+		return;
+
+//
+// don't scroll more than one tile per frame
+//
+	if (xscroll >= 0x100)
+	{
+		xscroll = 0xFF;
+	}
+	else if (xscroll <= -0x100)
+	{
+		xscroll = -0xFF;
+	}
+	if (yscroll >= 0x100)
+	{
+		yscroll = 0xFF;
+	}
+	else if (yscroll <= -0x100)
+	{
+		yscroll = -0xFF;
+	}
+	RF_Scroll(xscroll, yscroll);
+
+//
+// update limits for onscreen and inactivate checks
+//
+	originxtilemax = (originxtile + PORTTILESWIDE) - 1;
+	originytilemax = (originytile + PORTTILESHIGH) - 1;
+	inactivateleft = originxtile - INACTIVATEDIST;
+	if (inactivateleft < 0)
+	{
+		inactivateleft = 0;
+	}
+	inactivateright = originxtilemax + INACTIVATEDIST;
+	if (inactivateright < 0)
+	{
+		inactivateright = 0;
+	}
+	inactivatetop = originytile - INACTIVATEDIST;
+	if (inactivatetop < 0)
+	{
+		inactivatetop = 0;
+	}
+	inactivatebottom = originytilemax + INACTIVATEDIST;
+	if (inactivatebottom < 0)
+	{
+		inactivatebottom = 0;
+	}
+}
+
+//===========================================================================
+
+
+/*
+#############################################################################
+
+				  The objarray data structure
+
+#############################################################################
+
+Objarray contains structures for every actor currently playing.  The structure
+is accessed as a linked list starting at *player, ending when ob->next ==
+NULL.  GetNewObj inserts a new object at the end of the list, meaning that
+if an actor spawns another actor, the new one WILL get to think and react the
+same frame.  RemoveObj unlinks the given object and returns it to the free
+list, but does not damage the objects ->next pointer, so if the current object
+removes itself, a linked list following loop can still safely get to the
+next element.
+
+<backwardly linked free list>
+
+#############################################################################
+*/
+
+
+/*
+=========================
+=
+= InitObjArray
+=
+= Call to clear out the entire object list, returning them all to the free
+= list.  Allocates a special spot for the player.
+=
+=========================
+*/
+
+void InitObjArray(void)
+{
+	Sint16 i;
+
+	for (i=0; i<MAXACTORS; i++)
+	{
+		objarray[i].prev = &objarray[i+1];
+		objarray[i].next = NULL;
+	}
+
+	objarray[MAXACTORS-1].prev = NULL;
+
+	objfreelist = &objarray[0];
+	lastobj = NULL;
+
+	objectcount = 0;
+
+//
+// give the player and score the first free spots
+//
+	GetNewObj(false);
+	player = new;
+	GetNewObj(false);
+	scoreobj = new;
+}
+
+//===========================================================================
+
+/*
+=========================
+=
+= GetNewObj
+=
+= Sets the global variable new to point to a free spot in objarray.
+= The free spot is inserted at the end of the liked list
+=
+= When the object list is full, the caller can either have it bomb out or
+= return a dummy object pointer that will never get used
+=
+= Returns -1 when list was full, otherwise returns 0.
+=
+=========================
+*/
+
+Sint16 GetNewObj(boolean usedummy)
+{
+	if (!objfreelist)
+	{
+		if (usedummy)
+		{
+			new = &dummyobj;
+			return -1;
+		}
+		Quit("GetNewObj: No free spots in objarray!");
+	}
+	new = objfreelist;
+	objfreelist = new->prev;
+	memset(new, 0, sizeof(*new));
+	if (lastobj)
+	{
+		lastobj->next = new;
+	}
+	new->prev = lastobj;	// new->next is allready NULL from memset
+
+	new->active = ac_yes;
+	new->needtoclip = cl_midclip;
+	lastobj = new;
+
+	objectcount++;
+	return 0;
+}
+
+//===========================================================================
+
+/*
+=========================
+=
+= RemoveObj
+=
+= Add the given object back into the free list, and unlink it from it's
+= neighbors
+=
+=========================
+*/
+
+void RemoveObj(objtype *ob)
+{
+	if (ob == player)
+		Quit("RemoveObj: Tried to remove the player!");
+
+//
+// erase it from the refresh manager
+//
+	RF_RemoveSprite(&ob->sprite);
+	if (ob->obclass == stunnedobj)
+	{
+		RF_RemoveSprite((void **)&ob->temp3);
+	}
+
+//
+// fix the next object's back link
+//
+	if (ob == lastobj)
+	{
+		lastobj = ob->prev;
+	}
+	else
+	{
+		ob->next->prev = ob->prev;
+	}
+
+//
+// fix the previous object's forward link
+//
+	ob->prev->next = ob->next;
+
+//
+// add it back in to the free list
+//
+	ob->prev = objfreelist;
+	objfreelist = ob;
+}
+
+//==========================================================================
+
+/*
+====================
+=
+= GivePoints
+=
+= Grants extra men at 20k,40k,80k,160k,320k
+=
+====================
+*/
+
+void GivePoints(Uint16 points)
+{
+	gamestate.score += points;
+	if (!DemoMode && gamestate.score >= gamestate.nextextra)
+	{
+		SD_PlaySound(SND_EXTRAKEEN);
+		gamestate.lives++;
+		gamestate.nextextra *= 2;
+	}
+}
+
+//==========================================================================
+
+/*
+===================
+=
+= PollControls
+=
+===================
+*/
+
+void PollControls(void)
+{
+	IN_ReadControl(0, &c);
+	if (c.yaxis != -1)
+		upheld = false;
+
+	if (GravisGamepad && !DemoMode)
+	{
+		jumpbutton = GravisAction[ga_Jump];
+		pogobutton = GravisAction[ga_Pogo];
+		firebutton = GravisAction[ga_Fire];
+		if (!jumpbutton)
+			jumpheld = false;
+		if (!pogobutton)
+			pogoheld = false;
+		if (!firebutton)
+			fireheld = false;
+	}
+	else if (oldshooting || DemoMode)
+	{
+		if (c.button0 && c.button1)
+		{
+			firebutton = true;
+			jumpbutton = pogobutton = jumpheld = pogoheld = false;
+		}
+		else
+		{
+			firebutton = fireheld = false;
+			if (c.button0)
+			{
+				jumpbutton = true;
+			}
+			else
+			{
+				jumpbutton = jumpheld = false;
+			}
+			if (c.button1)
+			{
+				if (oldfirecount <= 8)
+				{
+					oldfirecount = oldfirecount + tics;
+				}
+				else
+				{
+					pogobutton = true;
+				}
+			}
+			else
+			{
+				if (oldfirecount != 0)
+				{
+					pogobutton = true;
+				}
+				else
+				{
+					pogobutton = pogoheld = false;
+				}
+				oldfirecount = 0;
+			}
+		}
+	}
+	else
+	{
+		jumpbutton = c.button0;
+		pogobutton = c.button1;
+		firebutton = Keyboard[firescan];
+		if (!jumpbutton)
+			jumpheld = false;
+		if (!pogobutton)
+			pogoheld = false;
+		if (!firebutton)
+			fireheld = false;
+	}
+}
+
+//==========================================================================
+
+
+/*
+=================
+=
+= StopMusic
+=
+=================
+*/
+
+void StopMusic(void)
+{
+	Sint16 i;
+
+	SD_MusicOff();
+	for (i=0; i<LASTMUSIC; i++)
+	{
+		if (audiosegs[STARTMUSIC+i])
+		{
+#ifdef FIX_MUSIC_MEMORY_ISSUES
+			//unlock any music blocks so that they can be purged
+			MM_SetLock(&(memptr)audiosegs[STARTMUSIC+i], false);
+#endif
+			MM_SetPurge(&(memptr)audiosegs[STARTMUSIC+i], PURGE_FIRST);
+		}
+	}
+}
+
+//==========================================================================
+
+/*
+=================
+=
+= StartMusic
+=
+=================
+*/
+
+void StartMusic(Uint16 num)
+{
+	static Sint16 songs[] =
+	{
+#if defined KEEN4
+		SHADOWS_MUS,
+		KICKPANT_MUS,
+		OASIS_MUS,
+		OASIS_MUS,
+		TOOHOT_MUS,
+		TOOHOT_MUS,
+		KICKPANT_MUS,
+		OASIS_MUS,
+		VEGGIES_MUS,
+		VEGGIES_MUS,
+		VEGGIES_MUS,
+		TOOHOT_MUS,
+		TOOHOT_MUS,
+		TOOHOT_MUS,
+		TOOHOT_MUS,
+		TOOHOT_MUS,
+		TOOHOT_MUS,
+		VEGGIES_MUS,
+		OASIS_MUS,
+		-1
+#elif defined KEEN5
+		ROBOROCK_MUS,
+		WEDNESDY_MUS,
+		BREATHE_MUS,
+		SPHEREFUL_MUS,
+		TIGHTER_MUS,
+		SPHEREFUL_MUS,
+		TIGHTER_MUS,
+		SPHEREFUL_MUS,
+		TIGHTER_MUS,
+		SPHEREFUL_MUS,
+		TIGHTER_MUS,
+		SNOOPING_MUS,
+		FEARSOME_MUS,
+		BAGPIPES_MUS,
+		FANFARE_MUS,
+		SKATING_MUS,
+		ROCK_ME_MUS,
+		HAVING_T_MUS,
+		CAMEIN_MUS,
+		SHIKAIRE_MUS,
+#elif defined KEEN6
+		ALIENATE_MUS,
+		FASTER_MUS,
+		BRERTAR_MUS,
+		MAMSNAKE_MUS,
+		MAMSNAKE_MUS,
+		MAMSNAKE_MUS,
+		METAL_MUS,
+		TOFUTURE_MUS,
+		METAL_MUS,
+		BRERTAR_MUS,
+		FASTER_MUS,
+		TOFUTURE_MUS,
+		BRERTAR_MUS,
+		SPACFUNK_MUS,
+		SPACFUNK_MUS,
+		OMINOUS_MUS,
+		TOFUTURE_MUS,
+		WONDER_MUS,
+		WONDER_MUS,
+		WONDER_MUS
+#endif
+	};
+
+	Sint16 song;
+	boolean wasfaded;
+
+	if (num >= ARRAYLENGTH(songs) && num != 0xFFFF)
+	{
+		Quit("StartMusic() - bad level number");
+	}
+
+#ifdef FIX_MUSIC_MEMORY_ISSUES
+	StopMusic();
+#else
+	SD_MusicOff();
+#endif
+
+#ifdef KEEN4
+	if (num == 0xFFFF)
+	{
+		song = WONDER_MUS;
+	}
+	else
+	{
+		song = songs[num];
+	}
+#else
+	song = songs[num];
+#endif
+
+	if (song == -1 || MusicMode != smm_AdLib)
+	{
+		return;
+	}
+
+	MM_BombOnError(false);
+	CA_CacheAudioChunk(STARTMUSIC+song);
+	MM_BombOnError(true);
+	if (mmerror)
+	{
+		mmerror = false;
+		if (!DemoMode)
+		{
+			US_CenterWindow(20, 8);
+			PrintY += 20;
+			US_CPrint("Insufficient memory\nfor background music!");
+			VW_UpdateScreen();
+			wasfaded = screenfaded;
+			if (wasfaded)
+			{
+				VW_SetDefaultColors();
+			}
+			IN_ClearKeysDown();
+			IN_UserInput(3*TickBase, false);
+			if (wasfaded)
+			{
+				VW_FadeOut();
+			}
+		}
+	}
+	else
+	{
+#ifdef FIX_MUSIC_MEMORY_ISSUES
+		//The current music should be locked, so the memory manager will not
+		//mess with it when compressing memory blocks in MM_SortMem().
+		MM_SetLock(&(memptr)audiosegs[STARTMUSIC+song], true);
+#endif
+		SD_StartMusic((MusicGroup far *)audiosegs[STARTMUSIC+song]);
+	}
+}
+
+//==========================================================================
+
+
+/*
+===================
+=
+= PlayLoop
+=
+===================
+*/
+
+void PlayLoop(void)
+{
+	objtype *check;
+
+	StartMusic(gamestate.mapon);
+	fireheld = pogoheld = upheld = jumpheld = false;
+	ingame = true;
+	playstate = ex_stillplaying;
+	invincible = keenkilled = oldfirecount = 0;
+
+	CenterActor(player);
+
+	if (DemoMode)
+	{
+		US_InitRndT(false);
+	}
+	else
+	{
+		US_InitRndT(true);
+	}
+	TimeCount = lasttimecount = tics = 3;
+
+	do
+	{
+		PollControls();
+
+//
+// go through state changes and propose movements
+//
+		for (obj=player; obj; obj=obj->next)
+		{
+			if (!obj->active && obj->tileright >= originxtile-1
+				&& obj->tileleft <= originxtilemax+1 && obj->tiletop <= originytilemax+1
+				&& obj->tilebottom >= originytile-1)
+			{
+				obj->needtoreact = true;
+				obj->active = ac_yes;
+			}
+			if (obj->active)
+			{
+				if (obj->tileright < inactivateleft
+					|| obj->tileleft > inactivateright
+					|| obj->tiletop > inactivatebottom
+					|| obj->tilebottom < inactivatetop)
+				{
+					if (obj->active == ac_removable)
+					{
+						RemoveObj(obj);
+						continue;
+					}
+					else if (obj->active != ac_allways)
+					{
+						if (US_RndT() < tics*2 || screenfaded || loadedgame)
+						{
+							RF_RemoveSprite(&obj->sprite);
+							if (obj->obclass == stunnedobj)
+								RF_RemoveSprite((void **)&obj->temp3);
+							obj->active = ac_no;
+							continue;
+						}
+					}
+				}
+				StateMachine(obj);
+			}
+		}
+
+		if (gamestate.riding)
+		{
+			HandleRiding(player);
+		}
+
+//
+// check for and handle collisions between objects
+//
+		for (obj=player; obj; obj=obj->next)
+		{
+			if (obj->active)
+			{
+				for (check=obj->next; check; check=check->next)
+				{
+					if (!check->active)
+					{
+						continue;
+					}
+					if (obj->right > check->left && obj->left < check->right
+						&& obj->top < check->bottom && obj->bottom > check->top)
+					{
+						if (obj->state->contact)
+						{
+							obj->state->contact(obj, check);
+						}
+						if (check->state->contact)
+						{
+							check->state->contact(check, obj);
+						}
+						if (obj->obclass == nothing)	//useless -- obclass is NOT set to nothing by RemoveObj
+						{
+							break;
+						}
+					}
+				}
+			}
+		}
+
+//
+// check intiles
+//
+		if (mapon != 0)
+		{
+			CheckInTiles(player);
+		}
+		else
+		{
+			CheckWorldInTiles(player);
+		}
+
+//
+// react to whatever happened, and post sprites to the refresh manager
+//
+		for (obj=player; obj; obj=obj->next)
+		{
+			if (!obj->active)
+			{
+				continue;
+			}
+			if (obj->tilebottom >= mapheight-1)
+			{
+				if (obj->obclass == keenobj)
+				{
+					playstate = ex_died;
+				}
+				else
+				{
+					RemoveObj(obj);
+				}
+				continue;
+			}
+			if (obj->needtoreact && obj->state->react)
+			{
+				obj->needtoreact = false;
+				obj->state->react(obj);
+			}
+		}
+
+//
+// scroll the screen and update the score box
+//
+#ifdef KEEN4
+		if (mapon != 0 && mapon != 17)
+#else
+		if (mapon != 0)
+#endif
+		{
+			ScrollScreen(player);
+		}
+		else
+		{
+			WorldScrollScreen(player);
+		}
+		UpdateScore(scoreobj);
+		if (loadedgame)
+		{
+			loadedgame = false;
+		}
+
+//
+// update the screen and calculate the number of tics it took to execute
+// this cycle of events (for adaptive timing of next cycle)
+//
+		RF_Refresh();
+
+		if (invincible)
+		{
+			if ((invincible = invincible - tics) < 0)
+				invincible = 0;
+		}
+
+#ifdef KEEN6
+		if (groundslam)
+		{
+			if ((groundslam = groundslam - tics) < 0)
+				groundslam = 0;
+		}
+#endif
+//
+// single step debug mode
+//
+		if (singlestep)
+		{
+			VW_WaitVBL(14);	//reduces framerate to 5 fps on VGA or 4.3 fps on EGA cards
+			lasttimecount = TimeCount;
+		}
+//
+// extra VBLs debug mode
+//
+		if (extravbls)
+		{
+			VW_WaitVBL(extravbls);
+		}
+
+//
+// handle user inputs
+//
+		if (DemoMode == demo_Playback)
+		{
+			if (!screenfaded && IN_IsUserInput())
+			{
+				playstate = ex_completed;
+				if (LastScan != sc_F1)
+				{
+					LastScan = sc_Space;
+				}
+			}
+		}
+		else if (DemoMode == demo_PlayDone)
+		{
+			playstate = ex_completed;
+		}
+		else
+		{
+			CheckKeys();
+		}
+
+//
+// E-N-D cheat
+//
+		if (Keyboard[sc_E] && Keyboard[sc_N] && Keyboard[sc_D])
+		{
+#if defined KEEN4
+			gamestate.rescued = 7;
+			playstate = ex_rescued;
+#elif defined KEEN5
+			playstate = ex_qedbroke;
+#elif defined KEEN6
+			playstate = ex_molly;
+#endif
+		}
+
+	} while (playstate == ex_stillplaying);
+
+	ingame = false;
+	StopMusic();
+}
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/CK_STATE.C b/16/keen456/KEEN4-6/CK_STATE.C
new file mode 100755
index 00000000..25d3be69
--- /dev/null
+++ b/16/keen456/KEEN4-6/CK_STATE.C
@@ -0,0 +1,1968 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+#include "CK_DEF.H"
+
+/*
+=============================================================================
+
+						 GLOBAL VARIABLES
+
+=============================================================================
+*/
+
+Sint16 wallclip[8][16] = {			// the height of a given point in a tile
+{ 256, 256, 256, 256, 256, 256, 256, 256, 256, 256, 256, 256, 256, 256, 256, 256},
+{   0,   0,   0,   0,   0,   0,   0,   0,   0,   0,   0,   0,   0,   0,   0,   0},
+{   0,0x08,0x10,0x18,0x20,0x28,0x30,0x38,0x40,0x48,0x50,0x58,0x60,0x68,0x70,0x78},
+{0x80,0x88,0x90,0x98,0xa0,0xa8,0xb0,0xb8,0xc0,0xc8,0xd0,0xd8,0xe0,0xe8,0xf0,0xf8},
+{   0,0x10,0x20,0x30,0x40,0x50,0x60,0x70,0x80,0x90,0xa0,0xb0,0xc0,0xd0,0xe0,0xf0},
+{0x78,0x70,0x68,0x60,0x58,0x50,0x48,0x40,0x38,0x30,0x28,0x20,0x18,0x10,0x08,   0},
+{0xf8,0xf0,0xe8,0xe0,0xd8,0xd0,0xc8,0xc0,0xb8,0xb0,0xa8,0xa0,0x98,0x90,0x88,0x80},
+{0xf0,0xe0,0xd0,0xc0,0xb0,0xa0,0x90,0x80,0x70,0x60,0x50,0x40,0x30,0x20,0x10,   0}
+};
+
+Sint16 xtry, ytry;
+boolean playerkludgeclipcancel;
+
+/*
+=============================================================================
+
+						 LOCAL VARIABLES
+
+=============================================================================
+*/
+
+Uint16 oldtileleft, oldtiletop, oldtileright, oldtilebottom, oldtilemidx;
+Uint16 oldleft, oldtop, oldright, oldbottom, oldmidx;
+Sint16 leftmoved, topmoved, rightmoved, bottommoved, midxmoved;
+
+//==========================================================================
+
+/*
+====================
+=
+= MoveObjVert
+=
+====================
+*/
+
+void MoveObjVert(objtype *ob, Sint16 ymove)
+{
+	ob->y += ymove;
+	ob->top += ymove;
+	ob->bottom += ymove;
+	ob->tiletop = CONVERT_GLOBAL_TO_TILE(ob->top);
+	ob->tilebottom = CONVERT_GLOBAL_TO_TILE(ob->bottom);
+}
+
+/*
+====================
+=
+= MoveObjHoriz
+=
+====================
+*/
+
+void MoveObjHoriz(objtype *ob, Sint16 xmove)
+{
+	//BUG? ob->midx is not adjusted in Keen 4 & 5
+	ob->x += xmove;
+	ob->left += xmove;
+	ob->right += xmove;
+#ifdef KEEN6
+	ob->midx += xmove;	//BUG? ob->tilemidx is not updated
+#endif
+	ob->tileleft = CONVERT_GLOBAL_TO_TILE(ob->left);
+	ob->tileright = CONVERT_GLOBAL_TO_TILE(ob->right);
+}
+
+//==========================================================================
+
+/*
+====================
+=
+= PlayerBottomKludge
+=
+====================
+*/
+
+void PlayerBottomKludge(objtype *ob)
+{
+	Uint16 far *map;
+	Uint16 wall, clip, xpix;
+	Sint16 xmove, ymove;
+
+	map = (Uint16 far *)mapsegs[1] + mapbwidthtable[ob->tilebottom-1]/2;
+	if (ob->xdir == 1)
+	{
+		xpix = 0;
+		map += ob->tileright;
+		xmove = ob->right - ob->midx;
+		if (tinf[*(map-mapwidth)+WESTWALL] || tinf[*map+WESTWALL])
+		{
+			return;
+		}
+	}
+	else
+	{
+		xpix = 15;
+		map += ob->tileleft;
+		xmove = ob->left - ob->midx;
+		if (tinf[*(map-mapwidth)+EASTWALL] || tinf[*map+EASTWALL])
+		{
+			return;
+		}
+	}
+	if ((_AX = tinf[*map+NORTHWALL]) != 0)	// the _AX = ... part is just to recreate the original code's quirks, feel free to delete this
+	{
+		return;
+	}
+	map += mapwidth;
+	if ((wall = tinf[*map+NORTHWALL]) != 1)
+	{
+		return;
+	}
+	clip = wallclip[wall&7][xpix];
+	ymove = CONVERT_TILE_TO_GLOBAL(ob->tilebottom) + clip - 1 -ob->bottom;
+	if (ymove <= 0 && ymove >= -bottommoved)
+	{
+		ob->hitnorth = wall;
+		MoveObjVert(ob, ymove);
+		MoveObjHoriz(ob, xmove);
+	}
+}
+
+/*
+====================
+=
+= PlayerTopKludge
+=
+====================
+*/
+
+void PlayerTopKludge(objtype *ob)
+{
+	Uint16 far *map;
+	Uint16 xpix, wall, clip;
+	Sint16 move;
+
+	map = (Uint16 far *)mapsegs[1] + mapbwidthtable[ob->tiletop+1]/2;
+	if (ob->xdir == 1)
+	{
+		xpix = 0;
+		map += ob->tileright;
+		if (tinf[*(map+mapwidth)+WESTWALL] || tinf[*(map+2*mapwidth)+WESTWALL])
+		{
+			return;
+		}
+	}
+	else
+	{
+		xpix = 15;
+		map += ob->tileleft;
+		if (tinf[*(map+mapwidth)+EASTWALL] || tinf[*(map+2*mapwidth)+EASTWALL])
+		{
+			return;
+		}
+	}
+	if ((_AX = tinf[*map+SOUTHWALL]) != 0)	// the _AX = ... part is just to recreate the original code's quirks, feel free to delete this
+	{
+		return;
+	}
+	map -= mapwidth;
+	if ((wall = tinf[*map+SOUTHWALL]) != 0)
+	{
+		clip = wallclip[wall&7][xpix];
+		move = CONVERT_TILE_TO_GLOBAL(ob->tiletop+1) - clip - ob->top;
+		if (move >= 0 && move <= -topmoved)
+		{
+			ob->hitsouth = wall;
+			MoveObjVert(ob, move);
+		}
+	}
+}
+
+/*
+===========================
+=
+= ClipToEnds
+=
+===========================
+*/
+
+void ClipToEnds(objtype *ob)
+{
+	Uint16 far *map;
+	Uint16 wall, y, clip;
+	Sint16 totalmove, maxmove, move;
+	Uint16 midxpix;
+	
+	midxpix = CONVERT_GLOBAL_TO_PIXEL(ob->midx & 0xF0);
+	maxmove = -abs(midxmoved)-bottommoved-16;
+	map = (Uint16 far *)mapsegs[1] + (mapbwidthtable-1)[oldtilebottom]/2 + ob->tilemidx;
+	for (y=oldtilebottom-1; y <= ob->tilebottom; y++,map+=mapwidth)
+	{
+		if ((wall = tinf[*map + NORTHWALL]) != 0)
+		{
+			clip = wallclip[wall&7][midxpix];
+			move = (CONVERT_TILE_TO_GLOBAL(y) + clip)-1-ob->bottom;
+			if (move < 0 && move >= maxmove)
+			{
+				ob->hitnorth = wall;
+				MoveObjVert(ob, move);
+				return;
+			}
+		}
+	}
+	maxmove = abs(midxmoved)-topmoved+16;
+	map = (Uint16 far *)mapsegs[1] + (mapbwidthtable+1)[oldtiletop]/2 + ob->tilemidx;
+	for (y=oldtiletop+1; y >= ob->tiletop; y--,map-=mapwidth)	// BUG: unsigned comparison - loop never ends if ob->tiletop is 0
+	{
+		if ((wall = tinf[*map + SOUTHWALL]) != 0)
+		{
+			clip = wallclip[wall&7][midxpix];
+			move = CONVERT_TILE_TO_GLOBAL(y+1) - clip - ob->top;
+			if (move > 0 && move <= maxmove)
+			{
+				totalmove = ytry+move;
+				if (totalmove < 0x100 && totalmove > -0x100)
+				{
+					ob->hitsouth = wall;
+					MoveObjVert(ob, move);
+					//BUG? no return here
+				}
+			}
+		}
+	}
+}
+
+/*
+===========================
+=
+= ClipToSides
+=
+===========================
+*/
+
+void ClipToSides(objtype *ob)
+{
+	Sint16 move, y, top, bottom;
+	Uint16 far *map;
+	
+	top = ob->tiletop;
+	if (ob->hitsouth > 1)
+	{
+		top++;
+	}
+	bottom = ob->tilebottom;
+	if (ob->hitnorth > 1)
+	{
+		bottom--;
+	}
+	for (y=top; y<=bottom; y++)
+	{
+		map = (Uint16 far *)mapsegs[1] + mapbwidthtable[y]/2 + ob->tileleft;
+		if ((ob->hiteast = tinf[*map+EASTWALL]) != 0)
+		{
+			move = CONVERT_TILE_TO_GLOBAL(ob->tileleft+1) - ob->left;
+			MoveObjHoriz(ob, move);
+			return;
+		}
+	}
+	for (y=top; y<=bottom; y++)
+	{
+		map = (Uint16 far *)mapsegs[1] + mapbwidthtable[y]/2 + ob->tileright;
+		if ((ob->hitwest = tinf[*map+WESTWALL]) != 0)
+		{
+			move = (CONVERT_TILE_TO_GLOBAL(ob->tileright)-1)-ob->right;
+			MoveObjHoriz(ob, move);
+			return;
+		}
+	}
+}
+
+/*
+===========================
+=
+= CheckPosition
+=
+===========================
+*/
+
+boolean CheckPosition(objtype *ob)
+{
+#ifdef KEEN6Ev15
+	// This version is pretty much a compiler-optimized version of the other
+	// version below, but I simply could not get the compiler to optimize it
+	// in exactly the same way.
+
+	Uint16 tile, x, tileright;
+	Uint16 far *map;
+	Uint16 rowdiff;
+	Uint16 tileleft, y, tilebottom;
+	
+	map = (Uint16 far *)mapsegs[1] + mapbwidthtable[ob->tiletop]/2 + ob->tileleft;
+	rowdiff = mapwidth-(ob->tileright-ob->tileleft+1);
+
+	y = ob->tiletop;
+	tileleft = ob->tileleft;
+	tileright = _AX = ob->tileright;
+	tilebottom = ob->tilebottom;
+
+	for (; tilebottom>=y; y++,map+=rowdiff)
+	{
+		for (x=tileleft; tileright>=x; x++)
+		{
+			tile = *(map++);
+			if (tinf[tile+NORTHWALL] || tinf[tile+EASTWALL] || tinf[tile+SOUTHWALL] || tinf[tile+WESTWALL])
+			{
+				return false;
+			}
+		}
+	}
+	return true;
+#else
+	Uint16 tile, x, y;
+	Uint16 far *map;
+	Uint16 rowdiff;
+	
+	map = (Uint16 far *)mapsegs[1] + mapbwidthtable[ob->tiletop]/2 + ob->tileleft;
+	rowdiff = mapwidth-(ob->tileright-ob->tileleft+1);
+	for (y=ob->tiletop; y<=ob->tilebottom; y++,map+=rowdiff)
+	{
+		for (x=ob->tileleft; x<=ob->tileright; x++)
+		{
+			tile = *(map++);
+			if (tinf[tile+NORTHWALL] || tinf[tile+EASTWALL] || tinf[tile+SOUTHWALL] || tinf[tile+WESTWALL])
+			{
+				return false;
+			}
+		}
+	}
+	return true;
+#endif
+}
+
+/*
+===========================
+=
+= StatePositionOk
+=
+===========================
+*/
+
+boolean StatePositionOk(objtype *ob, statetype *state)
+{
+	spritetabletype far *shape;
+
+	if (ob->xdir > 0)
+	{
+		ob->shapenum = state->rightshapenum;
+	}
+	else
+	{
+		ob->shapenum = state->leftshapenum;
+	}
+	shape = &spritetable[ob->shapenum-STARTSPRITES];
+	ob->left = ob->x + shape->xl;
+	ob->right = ob->x + shape->xh;
+	ob->top = ob->y + shape->yl;
+	ob->bottom = ob->y + shape->yh;
+	ob->midx = ob->left + (ob->right-ob->left)/2;
+	ob->tileleft = CONVERT_GLOBAL_TO_TILE(ob->left);
+	ob->tileright = CONVERT_GLOBAL_TO_TILE(ob->right);
+	ob->tiletop = CONVERT_GLOBAL_TO_TILE(ob->top);
+	ob->tilebottom = CONVERT_GLOBAL_TO_TILE(ob->bottom);
+	ob->tilemidx = CONVERT_GLOBAL_TO_TILE(ob->midx);
+	return CheckPosition(ob);
+}
+
+#ifdef KEEN5
+/*
+===========================
+=
+= CalcBounds
+=
+===========================
+*/
+
+void CalcBounds(objtype *ob)	//not present in Keen 4 & 6
+{
+	spritetabletype far *shape;
+
+	shape = &spritetable[ob->shapenum-STARTSPRITES];
+	ob->left = ob->x + shape->xl;
+	ob->right = ob->x + shape->xh;
+	ob->top = ob->y + shape->yl;
+	ob->bottom = ob->y + shape->yh;
+	ob->midx = ob->left + (ob->right-ob->left)/2;
+}
+#endif
+
+//==========================================================================
+
+/*
+================
+=
+= ClipToWalls
+=
+= Moves the current object xtry/ytry units, clipping to walls
+=
+================
+*/
+
+void ClipToWalls(objtype *ob)
+{
+	Uint16 oldx, oldy;
+#ifdef KEEN6
+	Uint16 y;
+#endif
+	spritetabletype far *shape;
+	boolean pushed;
+
+	oldx = ob->x;
+	oldy = ob->y;
+	pushed = false;
+
+//
+// make sure it stays in contact with a 45 degree slope
+//
+	if (ob->state->pushtofloor)
+	{
+		if (ob->hitnorth == 25)
+		{
+			ytry = 145;
+		}
+		else
+		{
+			if (xtry > 0)
+			{
+				ytry = xtry+16;
+			}
+			else
+			{
+				ytry = -xtry+16;
+			}
+			pushed = true;
+		}
+	}
+
+//
+// move the shape
+//
+	if (xtry > 239)
+	{
+		xtry = 239;
+	}
+	else if (xtry < -239)
+	{
+		xtry = -239;
+	}
+	if (ytry > 255)			// +16 for push to floor
+	{
+		ytry = 255;
+	}
+	else if (ytry < -239)
+	{
+		ytry = -239;
+	}
+
+	ob->x += xtry;
+	ob->y += ytry;
+
+	ob->needtoreact = true;
+
+	if (!ob->shapenum)				// can't get a hit rect with no shape!
+	{
+		return;
+	}
+
+	shape = &spritetable[ob->shapenum-STARTSPRITES];
+
+	oldtileright = ob->tileright;
+	oldtiletop = ob->tiletop;
+	oldtileleft = ob->tileleft;
+	oldtilebottom = ob->tilebottom;
+	oldtilemidx = ob->tilemidx;
+
+	oldright = ob->right;
+	oldtop = ob->top;
+	oldleft = ob->left;
+	oldbottom = ob->bottom;
+	oldmidx = ob->midx;
+
+	ob->left = ob->x + shape->xl;
+	ob->right = ob->x + shape->xh;
+	ob->top = ob->y + shape->yl;
+	ob->bottom = ob->y + shape->yh;
+	ob->midx = ob->left + (ob->right-ob->left)/2;
+
+	ob->tileleft = CONVERT_GLOBAL_TO_TILE(ob->left);
+	ob->tileright = CONVERT_GLOBAL_TO_TILE(ob->right);
+	ob->tiletop = CONVERT_GLOBAL_TO_TILE(ob->top);
+	ob->tilebottom = CONVERT_GLOBAL_TO_TILE(ob->bottom);
+	ob->tilemidx = CONVERT_GLOBAL_TO_TILE(ob->midx);
+
+	ob->hitnorth=ob->hiteast=ob->hitsouth=ob->hitwest=0;
+
+	if (ob->needtoclip)
+	{
+		leftmoved = ob->left - oldleft;
+		rightmoved = ob->right - oldright;
+		topmoved = ob->top - oldtop;
+		bottommoved = ob->bottom - oldbottom;
+		midxmoved = ob->midx - oldmidx;
+
+	//
+	// clip it
+	//
+		ClipToEnds(ob);
+
+		if (ob == player && !playerkludgeclipcancel)	// zero tolerance near the edge when player gets pushed!
+		{
+			if (!ob->hitnorth && bottommoved > 0)
+			{
+				PlayerBottomKludge(ob);
+			}
+			if (!ob->hitsouth && topmoved < 0)
+			{
+				PlayerTopKludge(ob);
+			}
+		}
+		ClipToSides(ob);
+
+#ifdef KEEN6
+		//
+		// special hack to prevent player from getting stuck on slopes?
+		//
+		if (ob == player && (ob->hitnorth & 7) > 1 && (ob->hiteast || ob->hitwest))
+		{
+			Uint16 far *map;
+			Uint16 pixx, clip, move;
+			Uint16 wall;
+
+			pixx = CONVERT_GLOBAL_TO_PIXEL(ob->midx & (15*PIXGLOBAL));
+			map = (Uint16 far *)mapsegs[1] + mapbwidthtable[oldtilebottom]/2 + ob->tilemidx;
+
+			for (y=oldtilebottom; ob->tilebottom+1 >= y; y++, map+=mapwidth)
+			{
+				if ((wall = tinf[*map + NORTHWALL]) != 0)
+				{
+					clip = wallclip[wall & 7][pixx];
+					move = CONVERT_TILE_TO_GLOBAL(y) + clip - 1 - ob->bottom;
+					ob->hitnorth = wall;
+					MoveObjVert(ob, move);
+					return;
+				}
+			}
+		}
+#endif
+	}
+	if (pushed && !ob->hitnorth)
+	{
+		ob->y = oldy;
+		ob->x = oldx + xtry;
+
+		ob->left = ob->x + shape->xl;
+		ob->right = ob->x + shape->xh;
+		ob->top = ob->y + shape->yl;
+		ob->bottom = ob->y + shape->yh;
+		ob->midx = ob->left + (ob->right-ob->left)/2;
+
+		ob->tileleft = CONVERT_GLOBAL_TO_TILE(ob->left);
+		ob->tileright = CONVERT_GLOBAL_TO_TILE(ob->right);
+		ob->tiletop = CONVERT_GLOBAL_TO_TILE(ob->top);
+		ob->tilebottom = CONVERT_GLOBAL_TO_TILE(ob->bottom);
+		ob->tilemidx = CONVERT_GLOBAL_TO_TILE(ob->midx);
+	}
+
+	ob->xmove = ob->xmove + (ob->x - oldx);
+	ob->ymove = ob->ymove + (ob->y - oldy);
+}
+
+/*
+================
+=
+= FullClipToWalls
+=
+= Moves the current object xtry/ytry units, clipping to walls
+=
+================
+*/
+
+void FullClipToWalls(objtype *ob)
+{
+	Uint16 oldx, oldy, w, h;
+	spritetabletype far *shape;
+
+	oldx = ob->x;
+	oldy = ob->y;
+
+//
+// move the shape
+//
+	if (xtry > 239)
+	{
+		xtry = 239;
+	}
+	else if (xtry < -239)
+	{
+		xtry = -239;
+	}
+	if (ytry > 239)
+	{
+		ytry = 239;
+	}
+	else if (ytry < -239)
+	{
+		ytry = -239;
+	}
+
+	ob->x += xtry;
+	ob->y += ytry;
+
+	ob->needtoreact = true;
+
+	shape = &spritetable[ob->shapenum-STARTSPRITES];
+
+	switch (ob->obclass)
+	{
+#if defined KEEN4
+	case keenobj:
+		w = 40*PIXGLOBAL;
+		h = 24*PIXGLOBAL;
+		break;
+	case eggbirdobj:
+		w = 64*PIXGLOBAL;
+		h = 32*PIXGLOBAL;
+		break;
+	case dopefishobj:
+		w = 88*PIXGLOBAL;
+		h = 64*PIXGLOBAL;
+		break;
+	case schoolfishobj:
+		w = 16*PIXGLOBAL;
+		h = 8*PIXGLOBAL;
+		break;
+#elif defined KEEN5
+	case slicestarobj:
+	case spherefulobj:
+		w = h = 32*PIXGLOBAL;
+		break;
+#elif defined KEEN6
+	case blorbobj:
+		w = h = 32*PIXGLOBAL;
+		break;
+#endif
+
+	default:
+		Quit("FullClipToWalls: Bad obclass");
+		break;
+	}
+
+	ob->right = ob->x + w;
+	ob->left = ob->x;
+	ob->top = ob->y;
+	ob->bottom = ob->y + h;
+
+	ob->tileleft = CONVERT_GLOBAL_TO_TILE(ob->left);
+	ob->tileright = CONVERT_GLOBAL_TO_TILE(ob->right);
+	ob->tiletop = CONVERT_GLOBAL_TO_TILE(ob->top);
+	ob->tilebottom = CONVERT_GLOBAL_TO_TILE(ob->bottom);
+
+	ob->hitnorth=ob->hiteast=ob->hitsouth=ob->hitwest=0;
+
+//
+// clip it
+//
+	if (!CheckPosition(ob))
+	{
+		MoveObjHoriz(ob, -xtry);	//undo x movement
+		if (CheckPosition(ob))
+		{
+			if (xtry > 0)
+			{
+				ob->hitwest = 1;
+			}
+			else
+			{
+				ob->hiteast = 1;
+			}
+		}
+		else
+		{
+			if (ytry > 0)
+			{
+				ob->hitnorth = 1;
+			}
+			else
+			{
+				ob->hitsouth = 1;
+			}
+			MoveObjHoriz(ob, xtry);	//redo x movement
+			MoveObjVert(ob, -ytry);	//undo y movement
+			if (!CheckPosition(ob))
+			{
+				MoveObjHoriz(ob, -xtry);	//undo x movement
+				if (xtry > 0)
+				{
+					ob->hitwest = 1;
+				}
+				else
+				{
+					ob->hiteast = 1;
+				}
+			}
+		}
+	}
+
+	ob->xmove = ob->xmove + (ob->x - oldx);
+	ob->ymove = ob->ymove + (ob->y - oldy);
+
+	ob->left = ob->x + shape->xl;
+	ob->right = ob->x + shape->xh;
+	ob->top = ob->y + shape->yl;
+	ob->bottom = ob->y + shape->yh;
+	ob->midx = ob->left + (ob->right-ob->left)/2;
+}
+
+/*
+================
+=
+= PushObj
+=
+= Moves the current object xtry/ytry units, clipping to walls
+=
+================
+*/
+
+void PushObj(objtype *ob)
+{
+	Uint16 oldx, oldy;
+	spritetabletype far *shape;
+	
+	oldx = ob->x;
+	oldy = ob->y;
+
+//
+// move the shape
+//
+	ob->x += xtry;
+	ob->y += ytry;
+
+	ob->needtoreact = true;
+
+	if (!ob->shapenum)				// can't get a hit rect with no shape!
+	{
+		return;
+	}
+
+	shape = &spritetable[ob->shapenum-STARTSPRITES];
+
+	oldtileright = ob->tileright;
+	oldtiletop = ob->tiletop;
+	oldtileleft = ob->tileleft;
+	oldtilebottom = ob->tilebottom;
+	oldtilemidx = ob->tilemidx;
+
+	oldright = ob->right;
+	oldtop = ob->top;
+	oldleft = ob->left;
+	oldbottom = ob->bottom;
+	oldmidx = ob->midx;
+
+	ob->left = ob->x + shape->xl;
+	ob->right = ob->x + shape->xh;
+	ob->top = ob->y + shape->yl;
+	ob->bottom = ob->y + shape->yh;
+	ob->midx = ob->left + (ob->right-ob->left)/2;
+
+	ob->tileleft = CONVERT_GLOBAL_TO_TILE(ob->left);
+	ob->tileright = CONVERT_GLOBAL_TO_TILE(ob->right);
+	ob->tiletop = CONVERT_GLOBAL_TO_TILE(ob->top);
+	ob->tilebottom = CONVERT_GLOBAL_TO_TILE(ob->bottom);
+	ob->tilemidx = CONVERT_GLOBAL_TO_TILE(ob->midx);
+
+	if (ob->needtoclip)
+	{
+		leftmoved = ob->left - oldleft;
+		rightmoved = ob->right - oldright;
+		topmoved = ob->top - oldtop;
+		bottommoved = ob->bottom - oldbottom;
+		midxmoved = ob->midx - oldmidx;
+
+		ClipToEnds(ob);
+		ClipToSides(ob);
+	}
+
+	ob->xmove = ob->xmove + (ob->x - oldx);
+	ob->ymove = ob->ymove + (ob->y - oldy);
+}
+
+//==========================================================================
+
+
+/*
+==================
+=
+= ClipToSpriteSide
+=
+= Clips push to solid
+=
+==================
+*/
+
+void ClipToSpriteSide(objtype *push, objtype *solid)
+{
+	Sint16 xmove, leftinto, rightinto;
+
+	//
+	// amount the push shape can be pushed
+	//
+	xmove = solid->xmove - push->xmove;
+
+	//
+	// amount it is inside
+	//
+	leftinto = solid->right - push->left;
+	rightinto = push->right - solid->left;
+
+	if (leftinto > 0 && leftinto <= xmove)
+	{
+		xtry = leftinto;
+		if (push->state->pushtofloor)
+		{
+			ytry = leftinto+16;
+		}
+		ClipToWalls(push);
+		push->hiteast = 1;
+	}
+	else if (rightinto > 0 && rightinto <= -xmove)
+	{
+		xtry = -rightinto;
+		if (push->state->pushtofloor)
+		{
+			ytry = rightinto+16;
+		}
+		ClipToWalls(push);
+		push->hitwest = 1;
+	}
+}
+
+//==========================================================================
+
+
+/*
+==================
+=
+= ClipToSpriteTop
+=
+= Clips push to solid
+=
+==================
+*/
+
+void ClipToSpriteTop(objtype *push, objtype *solid)
+{
+	Sint16 temp, ymove, bottominto;
+
+	//
+	// amount the push shape can be pushed
+	//
+	ymove = push->ymove - solid->ymove;
+
+	//
+	// amount it is inside
+	//
+	bottominto = push->bottom - solid->top;
+
+	if (bottominto >= 0 && bottominto <= ymove)
+	{
+		if (push == player)
+		{
+			gamestate.riding = solid;
+		}
+		ytry = -bottominto;
+		temp = push->state->pushtofloor;
+		push->state->pushtofloor = false;
+		ClipToWalls(push);
+		push->state->pushtofloor = temp;
+		if (!push->hitsouth)
+		{
+			push->hitnorth = 25;
+		}
+	}
+}
+
+//==========================================================================
+
+
+/*
+==================
+=
+= ClipToSprite
+=
+= Clips push to solid
+=
+==================
+*/
+
+void ClipToSprite(objtype *push, objtype *solid, boolean squish)
+{
+	Sint16 xmove, ymove, leftinto, rightinto, topinto, bottominto;
+	
+	xmove = solid->xmove - push->xmove;
+	xtry = ytry = 0;
+
+	//
+	// left / right
+	//
+	leftinto = solid->right - push->left;
+	rightinto = push->right - solid->left;
+
+	if (leftinto > 0 && xmove+1 >= leftinto)
+	{
+		xtry = leftinto;
+		push->xspeed = 0;
+		PushObj(push);
+		if (squish && push->hitwest)
+		{
+			KillKeen();
+		}
+		push->hiteast = 1;
+		return;
+	}
+	else if (rightinto > 0 && -xmove+1 >= rightinto)
+	{
+		xtry = -rightinto;
+		push->xspeed = 0;
+		PushObj(push);
+		if (squish && push->hiteast)
+		{
+			KillKeen();
+		}
+		push->hitwest = 1;
+		return;
+	}
+
+	//
+	// top / bottom
+	//
+	ymove = push->ymove - solid->ymove;
+	topinto = solid->bottom - push->top;
+	bottominto = push->bottom - solid->top;
+	if (bottominto >= 0 && bottominto <= ymove)
+	{
+		if (push == player)
+		{
+			gamestate.riding = solid;
+		}
+		ytry = -bottominto;
+		PushObj(push);
+		if (squish && push->hitsouth)
+		{
+			KillKeen();
+		}
+		if (!push->hitsouth)
+		{
+			push->hitnorth = 25;
+		}
+		return;
+	}
+	else if (topinto >= 0 && topinto <= ymove)	// BUG: should be 'topinto <= -ymove'
+	{
+		ytry = topinto;
+		ClipToWalls(push);
+		if (squish && push->hitnorth)
+		{
+			KillKeen();
+		}
+		push->hitsouth = 25;
+	}
+}
+
+//==========================================================================
+
+
+/*
+==================
+=
+= DoActor
+=
+= Moves an actor in its current state by a given number of tics.
+= If that time takes it into the next state, it changes the state
+= and returns the number of excess tics after the state change
+=
+==================
+*/
+
+Sint16 DoActor(objtype *ob, Sint16 numtics)
+{
+	Sint16 ticcount, usedtics, excesstics;
+	statetype *state;
+	
+	state = ob->state;
+
+	if (state->progress == think)
+	{
+		if (state->think)
+		{
+			if (ob->nothink)
+			{
+				ob->nothink--;
+			}
+			else
+			{
+				state->think(ob);
+			}
+		}
+		return 0;
+	}
+
+	ticcount = ob->ticcount + numtics;
+
+	if (state->tictime > ticcount || state->tictime == 0)
+	{
+		ob->ticcount = ticcount;
+		if (state->progress == slide || state->progress == slidethink)
+		{
+			if (ob->xdir)
+			{
+				xtry += ob->xdir == 1? numtics*state->xmove : -numtics*state->xmove;
+			}
+			if (ob->ydir)
+			{
+				ytry += ob->ydir == 1? numtics*state->ymove : -numtics*state->ymove;
+			}
+		}
+		if ((state->progress == slidethink || state->progress == stepthink) && state->think)
+		{
+			if (ob->nothink)
+			{
+				ob->nothink--;
+			}
+			else
+			{
+				state->think(ob);
+			}
+		}
+		return 0;
+	}
+	else
+	{
+		usedtics = state->tictime - ob->ticcount;
+		excesstics = ticcount - state->tictime;
+		ob->ticcount = 0;
+		if (state->progress == slide || state->progress == slidethink)
+		{
+			if (ob->xdir)
+			{
+				xtry += ob->xdir == 1? usedtics*state->xmove : -usedtics*state->xmove;
+			}
+			if (ob->ydir)
+			{
+				ytry += ob->ydir == 1? usedtics*state->ymove : -usedtics*state->ymove;
+			}
+		}
+		else
+		{
+			if (ob->xdir)
+			{
+				xtry += ob->xdir == 1? state->xmove : -state->xmove;
+			}
+			if (ob->ydir)
+			{
+				ytry += ob->ydir == 1? state->ymove : -state->ymove;
+			}
+		}
+
+		if (state->think)
+		{
+			if (ob->nothink)
+			{
+				ob->nothink--;
+			}
+			else
+			{
+				state->think(ob);
+			}
+		}
+
+		if (state == ob->state)
+		{
+			ob->state = state->nextstate;	// go to next state
+		}
+		else if (!ob->state)
+		{
+			return 0;			// object removed itself
+		}
+		return excesstics;
+	}
+}
+
+//==========================================================================
+
+
+/*
+====================
+=
+= StateMachine
+=
+= Change state and give directions
+=
+====================
+*/
+
+void StateMachine(objtype *ob)
+{
+	Sint16 excesstics, oldshapenum;
+	statetype *state;
+	
+	ob->xmove=ob->ymove=xtry=ytry=0;
+	oldshapenum = ob->shapenum;
+
+	state = ob->state;
+
+	excesstics = DoActor(ob, tics);
+	if (ob->state != state)
+	{
+		ob->ticcount = 0;		// start the new state at 0, then use excess
+		state = ob->state;
+	}
+
+	while (excesstics)
+	{
+	//
+	// passed through to next state
+	//
+		if (!state->skippable && state->tictime <= excesstics)
+		{
+			excesstics = DoActor(ob, state->tictime-1);
+		}
+		else
+		{
+			excesstics = DoActor(ob, excesstics);
+		}
+		if (ob->state != state)
+		{
+			ob->ticcount = 0;		// start the new state at 0, then use excess
+			state = ob->state;
+		}
+	}
+
+	if (!state)			// object removed itself
+	{
+		RemoveObj(ob);
+		return;
+	}
+
+	//
+	// if state->rightshapenum == NULL, the state does not have a standard
+	// shape (the think routine should have set it)
+	//
+	if (state->rightshapenum)
+	{
+		if (ob->xdir > 0)
+		{
+			ob->shapenum = state->rightshapenum;
+		}
+		else
+		{
+			ob->shapenum = state->leftshapenum;
+		}
+	}
+	if ((Sint16)ob->shapenum == -1)
+	{
+		ob->shapenum = 0;		// make it invisable this time
+	}
+
+	if (xtry || ytry || ob->shapenum != oldshapenum || ob->hitnorth == 25)
+	{
+	//
+	// actor moved or changed shape
+	// make sure the movement is within limits (one tile)
+	//
+		if (ob->needtoclip == cl_fullclip)
+		{
+			FullClipToWalls(ob);
+		}
+		else
+		{
+			ClipToWalls(ob);
+		}
+	}
+}
+
+//==========================================================================
+
+
+/*
+====================
+=
+= NewState
+=
+====================
+*/
+
+void NewState(objtype *ob, statetype *state)
+{
+	Sint16 temp;
+	
+	ob->state = state;
+
+	if (state->rightshapenum)
+	{
+		if (ob->xdir > 0)
+		{
+			ob->shapenum = state->rightshapenum;
+		}
+		else
+		{
+			ob->shapenum = state->leftshapenum;
+		}
+	}
+
+	if ((Sint16)ob->shapenum == -1)
+	{
+		ob->shapenum = 0;
+	}
+
+	temp = ob->needtoclip;
+	ob->needtoclip = cl_noclip;
+
+	xtry = ytry = 0;					// no movement
+	ClipToWalls(ob);					// just calculate values
+
+	ob->needtoclip = temp;
+
+	if (ob->needtoclip == cl_fullclip)
+	{
+		FullClipToWalls(ob);
+	}
+	else if (ob->needtoclip == cl_midclip)
+	{
+		ClipToWalls(ob);
+	}
+}
+
+//==========================================================================
+
+
+/*
+====================
+=
+= ChangeState
+=
+====================
+*/
+
+void ChangeState(objtype *ob, statetype *state)
+{
+	ob->state = state;
+	ob->ticcount = 0;
+	if (state->rightshapenum)
+	{
+		if (ob->xdir > 0)
+		{
+			ob->shapenum = state->rightshapenum;
+		}
+		else
+		{
+			ob->shapenum = state->leftshapenum;
+		}
+	}
+
+	if ((Sint16)ob->shapenum == -1)
+	{
+		ob->shapenum = 0;
+	}
+
+	ob->needtoreact = true;			// it will need to be redrawn this frame
+
+	xtry = ytry = 0;					// no movement
+
+	if (ob->hitnorth != 25)
+	{
+		ClipToWalls(ob);
+	}
+}
+
+//==========================================================================
+
+
+/*
+====================
+=
+= OnScreen
+=
+====================
+*/
+
+boolean OnScreen(objtype *ob)
+{
+	if (ob->tileright < originxtile || ob->tilebottom < originytile
+		|| ob->tileleft > originxtilemax || ob->tiletop > originytilemax)
+	{
+		return false;
+	}
+	return true;
+}
+
+//==========================================================================
+
+
+/*
+====================
+=
+= DoGravity
+=
+====================
+*/
+
+void DoGravity(objtype *ob)
+{
+	Sint32 i;
+//
+// only accelerate on odd tics, because of limited precision
+//
+	for (i = lasttimecount-tics; i<lasttimecount; i++)
+	{
+		if (i&1)
+		{
+			if (ob->yspeed < 0 && ob->yspeed >= -4)
+			{
+				ytry += ob->yspeed;
+				ob->yspeed = 0;
+				return;
+			}
+			ob->yspeed += 4;
+			if (ob->yspeed > 70)
+			{
+				ob->yspeed = 70;
+			}
+		}
+		ytry += ob->yspeed;
+	}
+}
+
+
+/*
+====================
+=
+= DoWeakGravity
+=
+====================
+*/
+
+void DoWeakGravity(objtype *ob)
+{
+	Sint32 i;
+//
+// only accelerate on odd tics, because of limited precision
+//
+	for (i = lasttimecount-tics; i<lasttimecount; i++)
+	{
+		if (i&1)
+		{
+			if (ob->yspeed < 0 && ob->yspeed >= -3)
+			{
+				ytry += ob->yspeed;
+				ob->yspeed = 0;
+				return;
+			}
+			ob->yspeed += 3;
+			if (ob->yspeed > 70)
+			{
+				ob->yspeed = 70;
+			}
+		}
+		ytry += ob->yspeed;
+	}
+}
+
+
+/*
+====================
+=
+= DoTinyGravity
+=
+====================
+*/
+
+void DoTinyGravity(objtype *ob)
+{
+	Sint32 i;
+//
+// only accelerate every 4 tics, because of limited precision
+//
+	for (i = lasttimecount-tics; i<lasttimecount; i++)
+	{
+		if (!i & 3)	//BUG: this is equal to ((!i) & 3), not (!(i & 3))
+		{
+			ob->yspeed++;
+			if (ob->yspeed > 70)
+			{
+				ob->yspeed = 70;
+			}
+		}
+		ytry += ob->yspeed;
+	}
+}
+
+
+/*
+===============
+=
+= AccelerateX
+=
+===============
+*/
+
+void AccelerateX(objtype *ob, Sint16 dir, Sint16 maxspeed)
+{
+	Sint32 i;
+	Uint16 oldsign;
+	
+	oldsign = ob->xspeed & 0x8000;
+//
+// only accelerate on odd tics, because of limited precision
+//
+	for (i=lasttimecount-tics; i<lasttimecount; i++)
+	{
+		if (i & 1)
+		{
+			ob->xspeed += dir;
+			if ((ob->xspeed & 0x8000) != oldsign)
+			{
+				oldsign = ob->xspeed & 0x8000;
+				ob->xdir = oldsign? -1 : 1;
+			}
+			if (ob->xspeed > maxspeed)
+			{
+				ob->xspeed = maxspeed;
+			}
+			else if (ob->xspeed < -maxspeed)
+			{
+				ob->xspeed = -maxspeed;
+			}
+		}
+		xtry += ob->xspeed;
+	}
+}
+
+
+/*
+===============
+=
+= AccelerateXv
+=
+= Doesn't change object's xdir
+=
+===============
+*/
+
+void AccelerateXv(objtype *ob, Sint16 dir, Sint16 maxspeed)
+{
+	Sint32 i;
+
+//
+// only accelerate on odd tics, because of limited precision
+//
+	for (i=lasttimecount-tics; i<lasttimecount; i++)
+	{
+		if (i & 1)
+		{
+			ob->xspeed += dir;
+			if (ob->xspeed > maxspeed)
+			{
+				ob->xspeed = maxspeed;
+			}
+			else if (ob->xspeed < -maxspeed)
+			{
+				ob->xspeed = -maxspeed;
+			}
+		}
+		xtry += ob->xspeed;
+	}
+}
+
+
+/*
+===============
+=
+= AccelerateY
+=
+===============
+*/
+
+void AccelerateY(objtype *ob, Sint16 dir, Sint16 maxspeed)
+{
+	Sint32 i;
+
+//
+// only accelerate on odd tics, because of limited precision
+//
+	for (i=lasttimecount-tics; i<lasttimecount; i++)
+	{
+		if (i & 1)
+		{
+			ob->yspeed += dir;
+			if (ob->yspeed > maxspeed)
+			{
+				ob->yspeed = maxspeed;
+			}
+			else if (ob->yspeed < -maxspeed)
+			{
+				ob->yspeed = -maxspeed;
+			}
+		}
+		ytry += ob->yspeed;
+	}
+}
+
+
+/*
+===============
+=
+= FrictionX
+=
+===============
+*/
+
+void FrictionX(objtype *ob)
+{
+	Sint16 friction, oldsign;
+	Sint32 i;
+
+	oldsign = ob->xspeed & 0x8000;
+	if (ob->xspeed > 0)
+	{
+		friction = -1;
+	}
+	else if (ob->xspeed < 0)
+	{
+		friction = 1;
+	}
+	else
+	{
+		friction = 0;
+	}
+//
+// only accelerate on odd tics, because of limited precision
+//
+
+	for (i=lasttimecount-tics; i<lasttimecount; i++)
+	{
+		if (i & 1)
+		{
+			ob->xspeed += friction;
+			if ((ob->xspeed & 0x8000) != oldsign)
+			{
+				ob->xspeed = 0;
+			}
+		}
+		xtry += ob->xspeed;
+	}
+}
+
+
+/*
+===============
+=
+= FrictionY
+=
+===============
+*/
+
+void FrictionY(objtype *ob)
+{
+	Sint16 friction, oldsign;
+	Sint32 i;
+
+	if (ob->yspeed > 0)
+	{
+		friction = -1;
+	}
+	else if (ob->yspeed < 0)
+	{
+		friction = 1;
+	}
+	else
+	{
+		friction = 0;
+	}
+//
+// only accelerate on odd tics, because of limited precision
+//
+	for (i=lasttimecount-tics; i<lasttimecount; i++)
+	{
+		if (i & 1)
+		{
+			ob->yspeed += friction;
+			if ((ob->yspeed & 0x8000) != oldsign)	//BUG: oldsign is not initialized!
+			{
+				ob->yspeed = 0;
+			}
+		}
+		ytry += ob->yspeed;
+	}
+}
+
+//==========================================================================
+
+/*
+===============
+=
+= StunObj
+=
+===============
+*/
+
+void StunObj(objtype *ob, objtype *shot, statetype *stunstate)
+{
+	ExplodeShot(shot);
+	ob->temp1 = ob->temp2 = ob->temp3 = 0;	// Note: ob->nothink should also be set to 0
+	ob->temp4 = ob->obclass;
+	ChangeState(ob, stunstate);
+	ob->obclass = stunnedobj;
+#ifndef KEEN4
+	ob->yspeed -= 24;
+	if (ob->yspeed < -48)
+		ob->yspeed = -48;
+#endif
+}
+
+//==========================================================================
+
+/*
+===============
+=
+= T_Projectile
+=
+===============
+*/
+
+void T_Projectile(objtype *ob)
+{
+	DoGravity(ob);
+	xtry = ob->xspeed*tics;
+}
+
+
+/*
+===============
+=
+= T_WeakProjectile
+=
+===============
+*/
+
+void T_WeakProjectile(objtype *ob)
+{
+	DoWeakGravity(ob);
+	xtry = ob->xspeed*tics;
+}
+
+
+/*
+===============
+=
+= T_Velocity
+=
+===============
+*/
+
+void T_Velocity(objtype *ob)
+{
+	xtry = ob->xspeed*tics;
+	ytry = ob->yspeed*tics;
+}
+
+
+/*
+===============
+=
+= SetReactThink
+=
+===============
+*/
+
+void SetReactThink(objtype *ob)
+{
+	ob->needtoreact = true;
+}
+
+
+/*
+===============
+=
+= T_Stunned
+=
+===============
+*/
+
+void T_Stunned(objtype *ob)
+{
+	ob->temp1 = 0;
+	ob->needtoreact = true;
+	if (++ob->temp2 == 3)
+		ob->temp2 = 0;
+}
+
+
+/*
+===============
+=
+= C_Lethal
+=
+===============
+*/
+
+void C_Lethal(objtype *ob, objtype *hit)
+{
+	ob++;			// shut up compiler
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+}
+
+
+/*
+===============
+=
+= R_Draw
+=
+===============
+*/
+
+void R_Draw(objtype *ob)
+{
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+
+/*
+===============
+=
+= R_Walk
+=
+===============
+*/
+
+void R_Walk(objtype *ob)
+{
+	if (ob->xdir == 1 && ob->hitwest)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = -1;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	else if (ob->xdir == -1 && ob->hiteast)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = 1;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	else if (!ob->hitnorth)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = -ob->xdir;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+
+/*
+===============
+=
+= R_WalkNormal
+=
+= Actor will not walk onto tiles with special (e.g. deadly) north walls
+=
+===============
+*/
+
+void R_WalkNormal(objtype *ob)
+{
+	if (ob->xdir == 1 && ob->hitwest)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = -1;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	else if (ob->xdir == -1 && ob->hiteast)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = 1;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	else if (!ob->hitnorth || (ob->hitnorth & ~7))
+	{
+		ob->x -= ob->xmove*2;
+		ob->xdir = -ob->xdir;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+
+/*
+===============
+=
+= BadState
+=
+===============
+*/
+
+void BadState(void)
+{
+	Quit("Object with bad state!");
+}
+
+
+/*
+===============
+=
+= R_Stunned
+=
+===============
+*/
+
+void R_Stunned(objtype *ob)
+{
+	Sint16 starx, stary;
+
+	if (ob->hitwest || ob->hiteast)
+		ob->xspeed = 0;
+
+	if (ob->hitsouth)
+		ob->yspeed = 0;
+
+	if (ob->hitnorth)
+	{
+		ob->xspeed = ob->yspeed = 0;
+		if (ob->state->nextstate)
+			ChangeState(ob, ob->state->nextstate);
+	}
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+
+	starx = stary = 0;
+	switch (ob->temp4)
+	{
+#if defined KEEN4
+	case mimrockobj:
+		stary = -4*PIXGLOBAL;
+		break;
+	case eggobj:
+		starx = 8*PIXGLOBAL;
+		stary = -8*PIXGLOBAL;
+		break;
+	case treasureeaterobj:
+		starx = 8*PIXGLOBAL;
+		break;
+	case bounderobj:
+		starx = 4*PIXGLOBAL;
+		stary = -8*PIXGLOBAL;
+		break;
+	case wormouthobj:
+		starx = 4*PIXGLOBAL;
+		stary = -350;	// -21.875 pixels (this one is a bit strange)
+		break;
+	case lickobj:
+		stary = -8*PIXGLOBAL;
+		break;
+	case inchwormobj:
+		starx = -4*PIXGLOBAL;
+		stary = -8*PIXGLOBAL;
+		break;
+	case slugobj:
+		stary = -8*PIXGLOBAL;
+		break;
+#elif defined KEEN5
+	case sparkyobj:
+		starx += 4*PIXGLOBAL;
+		break;
+	case amptonobj:
+		stary -= 8*PIXGLOBAL;
+		asm jmp done;		// just to recreate the original code's quirks, feel free to delete this
+		break;
+	case scottieobj:
+		stary -= 8*PIXGLOBAL;
+		break;
+#elif defined KEEN6
+	case blooguardobj:
+		starx = 16*PIXGLOBAL;
+		stary = -4*PIXGLOBAL;
+		break;
+	case flectobj:
+		starx = 4*PIXGLOBAL;
+		stary = -4*PIXGLOBAL;
+		break;
+	case bloogobj:
+	case nospikeobj:
+		starx = 8*PIXGLOBAL;
+		stary = -4*PIXGLOBAL;
+		break;
+	case bloogletobj:
+	case babobbaobj:
+		stary = -8*PIXGLOBAL;
+		break;
+	case fleexobj:
+		starx = 16*PIXGLOBAL;
+		stary = 8*PIXGLOBAL;
+		break;
+	case ceilickobj:
+		stary = 12*PIXGLOBAL;
+		break;
+	default:
+		Quit("No star spec for object!");
+#endif
+	}
+done:
+
+	ob->temp1 = ob->temp1 + tics;
+	if (ob->temp1 > 10)
+	{
+		ob->temp1 -= 10;
+		if (++ob->temp2 == 3)
+			ob->temp2 = 0;
+	}
+
+	RF_PlaceSprite((void **)&ob->temp3, ob->x+starx, ob->y+stary, ob->temp2+STUNSTARS1SPR, spritedraw, 3);
+}
+
+//==========================================================================
+
+statetype sc_deadstate = {0, 0, think, false, false, 0, 0, 0, NULL, NULL, NULL, NULL};
+#pragma warn -sus	//BadState is not a valid think/contact/react function. Nobody cares.
+statetype sc_badstate  = {0, 0, think, false, false, 0, 0, 0, &BadState, &BadState, &BadState, NULL};
+#pragma warn +sus
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/CK_TEXT.C b/16/keen456/KEEN4-6/CK_TEXT.C
new file mode 100755
index 00000000..d4fdf65a
--- /dev/null
+++ b/16/keen456/KEEN4-6/CK_TEXT.C
@@ -0,0 +1,971 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Wolfenstein 3-D Source Code
+ * Copyright (C) 1992 id Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+#include "CK_DEF.H"
+
+/*
+=============================================================================
+
+TEXT FORMATTING COMMANDS
+------------------------
+^C<hex digit>  			Change text color
+^E[enter]				End of layout (all pages)
+^G<y>,<x>,<pic>[enter]	Draw a graphic and push margins
+^P[enter]				start new page, must be the first chars in a layout
+^L<x>,<y>[ENTER]		Locate to a specific spot, x in pixels, y in lines
+
+=============================================================================
+*/
+
+/*
+=============================================================================
+
+						 LOCAL CONSTANTS
+
+=============================================================================
+*/
+
+#if GRMODE == CGAGR
+#ifdef KEEN5
+#define BACKCOLOR 2	// CGA magenta
+#else
+#define BACKCOLOR WHITE
+#endif
+#else
+#define BACKCOLOR RED
+#endif
+
+#define WORDLIMIT 80
+#define FONTHEIGHT 10
+#define TOPMARGIN 10
+#define BOTTOMMARGIN 10
+#define LEFTMARGIN 10
+#define RIGHTMARGIN 10
+#define PICMARGIN 8
+#define SPACEWIDTH 7
+#define TEXTROWS ((200-TOPMARGIN-BOTTOMMARGIN)/FONTHEIGHT)
+#define SCREENPIXWIDTH 320
+#define SCREENMID (SCREENPIXWIDTH/2)
+
+/*
+=============================================================================
+
+						 LOCAL VARIABLES
+
+=============================================================================
+*/
+
+Sint16 pagenum,numpages;
+Uint16 leftmargin[TEXTROWS],rightmargin[TEXTROWS];
+char far *text;
+Uint16 rowon;
+Sint16 picx,picy,picnum,picdelay;
+boolean layoutdone;
+
+Sint16 helpmenupos;
+
+//===========================================================================
+
+/*
+=====================
+=
+= RipToEOL
+=
+=====================
+*/
+
+void RipToEOL(void)
+{
+	while (*text++ != '\n');
+}
+
+
+/*
+=====================
+=
+= ParseNumber
+=
+=====================
+*/
+
+Sint16 ParseNumber(void)
+{
+	char c, buffer[80];
+	char *bufptr;
+
+//
+// scan until a number is found
+//
+	c = *text;
+	while (c < '0' || c > '9')
+		c = *++text;
+
+//
+// copy the number out
+//
+	bufptr = buffer;
+	do
+	{
+		*bufptr = c;
+		bufptr++;
+		text++;
+		c = *text;
+	} while (c >= '0' && c <= '9');
+	*bufptr = 0;
+
+	return atoi(buffer);
+}
+
+
+/*
+=====================
+=
+= ParsePicCommand
+=
+= Call with text pointing just after a ^P
+= Upon exit text points to the start of next line
+=
+=====================
+*/
+
+void ParsePicCommand(void)
+{
+	picy = ParseNumber();
+	picx = ParseNumber();
+	picnum = ParseNumber();
+	RipToEOL();
+}
+
+void ParseTimedCommand(void)
+{
+	picy = ParseNumber();
+	picx = ParseNumber();
+	picnum = ParseNumber();
+	picdelay = ParseNumber();
+	RipToEOL();
+}
+
+/*
+=====================
+=
+= TimedPicCommand
+=
+= Call with text pointing just after a ^P
+= Upon exit text points to the start of next line
+=
+=====================
+*/
+
+void TimedPicCommand(void)
+{
+	ParseTimedCommand();
+
+//
+// update the screen, and wait for time delay
+//
+#if GRMODE == CGAGR
+	VW_UpdateScreen();
+#else
+	VW_WaitVBL(1);
+	VW_ScreenToScreen(bufferofs, displayofs, 40, 200);
+#endif
+
+//
+// wait for time
+//
+	TimeCount = 0;
+	while (picdelay > TimeCount)
+	;
+
+//
+// draw pic
+//
+	VWB_DrawPic(picx & ~7, picy, picnum);
+}
+
+
+/*
+=====================
+=
+= HandleCommand
+=
+=====================
+*/
+
+void HandleCommand(void)
+{
+	Sint16 i,margin,top,bottom;
+	Sint16 picwidth,picheight,picmid;
+
+	switch (toupper(*(++text)))
+	{
+	case 'B':
+		picy = ParseNumber();
+		picx = ParseNumber();
+		picwidth = ParseNumber();
+		picheight = ParseNumber();
+		VWB_Bar(picx, picy, picwidth, picheight, BACKCOLOR);
+		RipToEOL();
+		break;
+
+	case 'P':		// ^P is start of next page, ^E is end of file
+	case 'E':
+		layoutdone = true;
+		text--;
+		break;
+
+	case 'C':		// ^c<hex digit> changes text color
+		i = toupper(*(++text));
+		if (i >= '0' && i <= '9')
+		{
+			fontcolor = i + 0 - '0';
+		}
+		else if (i >= 'A' && i <= 'F')
+		{
+			fontcolor = i + 10 - 'A';
+		}
+#if GRMODE == CGAGR
+		{
+			static Sint16 colormap[16] = {2, 0, 0, 0, 2, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, 0};
+			// Note: This mapping is a bit problematic for Keen 5 CGA,
+			// since some colors get mapped to CGA magenta, which is
+			// used as the background color in that version. Luckily
+			// those colors aren't used in the Keen 5 texts anyway.
+
+			fontcolor = colormap[fontcolor];
+		}
+#endif
+		fontcolor ^= BACKCOLOR;
+		text++;
+		break;
+
+	case 'L':
+		py = ParseNumber();
+		rowon = (py - 10)/10;
+		py = rowon * 10 + 10;
+		px = ParseNumber();
+		while (*(text++) != '\n')	// scan to end of line
+		;
+		break;
+
+	case 'T':		// ^Tyyy,xxx,ppp,ttt waits ttt tics, then draws pic
+		TimedPicCommand();
+		break;
+
+	case 'G':		// ^Gyyy,xxx,ppp draws graphic
+		ParsePicCommand();
+		VWB_DrawPic(picx & ~7, picy, picnum);
+		picwidth = pictable[picnum-STARTPICS].width * BYTEPIXELS;
+		picheight = pictable[picnum-STARTPICS].height;
+		picmid = picx + picwidth/2;
+		//
+		// adjust margins
+		//
+		if (picmid > SCREENMID)
+		{
+			margin = picx-PICMARGIN;			// new right margin
+		}
+		else
+		{
+			margin = picx+picwidth+PICMARGIN;	// new left margin
+		}
+		top = (picy-TOPMARGIN)/FONTHEIGHT;
+		if (top < 0)
+		{
+			top = 0;
+		}
+		bottom = (picy+picheight-TOPMARGIN)/FONTHEIGHT;
+		if (bottom >= TEXTROWS)
+		{
+			bottom = TEXTROWS-1;
+		}
+
+		for (i=top; i<=bottom; i++)
+		{
+			if (picmid > SCREENMID)
+			{
+				rightmargin[i] = margin;
+			}
+			else
+			{
+				leftmargin[i] = margin;
+			}
+		}
+
+		//
+		// adjust this line if needed
+		//
+		if (leftmargin[rowon] > px)
+		{
+			px = leftmargin[rowon];
+		}
+		break;
+	}
+}
+
+
+/*
+=====================
+=
+= NewLine
+=
+=====================
+*/
+
+void NewLine(void)
+{
+	char c;
+
+	if (++rowon == TEXTROWS)
+	{
+	//
+	// overflowed the page, so skip until next page break
+	//
+		layoutdone = true;
+		do
+		{
+			if (*text == '^')
+			{
+				c = toupper(text[1]);
+				if (c == 'E' || c == 'P')
+				{
+					layoutdone = true;
+					return;
+				}
+			}
+			text++;
+		} while (1);
+	}
+	px = leftmargin[rowon];
+	py += FONTHEIGHT;
+}
+
+
+/*
+=====================
+=
+= HandleCtrls
+=
+=====================
+*/
+
+void HandleCtrls(void)
+{
+	char c;
+
+	c = *(text++);			// get the character and advance
+
+	if (c == '\n')
+	{
+		NewLine();
+		return;
+	}
+}
+
+/*
+=====================
+=
+= HandleWord
+=
+=====================
+*/
+
+void HandleWord(void)
+{
+	Uint16 wwidth, wheight, newpos, wordindex;
+	char word[WORDLIMIT];
+
+	//
+	// copy the next word into [word]
+	//
+	word[0] = *(text++);
+	wordindex = 1;
+	while (*text > ' ')
+	{
+		word[wordindex] = *(text++);
+		if (++wordindex == WORDLIMIT)
+		{
+			Quit("PageLayout: Word limit exceeded");
+		}
+	}
+	word[wordindex] = 0;		// stick a null at end for C
+
+	//
+	// see if it fits on this line
+	//
+	VW_MeasurePropString(word, &wwidth, &wheight);
+	
+	while (rightmargin[rowon] < px+wwidth)
+	{
+		NewLine();
+		if (layoutdone)
+		{
+			return;		// overflowed page
+		}
+	}
+
+	//
+	// print it
+	//
+	newpos = px+wwidth;
+	VWB_DrawPropString(word);
+	px = newpos;
+
+	//
+	// suck up any extra spaces
+	//
+	while (*text == ' ')
+	{
+		px += SPACEWIDTH;
+		text++;
+	}
+}
+
+/*
+=====================
+=
+= PageLayout
+=
+= Clears the screen, draws the pics on the page, and word wraps the text.
+= Returns a pointer to the terminating command
+=
+=====================
+*/
+
+void PageLayout(boolean shownumber)
+{
+	Sint16 oldcolor, i;
+	char c;
+
+	oldcolor = fontcolor;
+
+#if GRMODE == CGAGR
+	fontcolor = BLACK^BACKCOLOR;
+#else
+	fontcolor = YELLOW^BACKCOLOR;
+#endif
+
+//
+// clear the screen
+//
+	VWB_Bar(0, 0, 320, 200, BACKCOLOR);
+#ifndef KEEN6
+	VWB_DrawPic(  0, 0, H_TOPWINDOWPIC);
+	VWB_DrawPic(  0, 8, H_LEFTWINDOWPIC);
+	VWB_DrawPic(312, 8, H_RIGHTWINDOWPIC);
+	if (shownumber)
+	{
+		VWB_DrawPic(8, 176, H_BOTTOMINFOPIC);
+	}
+	else
+	{
+		VWB_DrawPic(8, 192, H_BOTTOMWINDOWPIC);
+	}
+#endif
+
+	for (i=0; i<TEXTROWS; i++)
+	{
+		leftmargin[i] = LEFTMARGIN;
+		rightmargin[i] = SCREENPIXWIDTH-RIGHTMARGIN;
+	}
+
+	px = LEFTMARGIN;
+	py = TOPMARGIN;
+	rowon = 0;
+	layoutdone = false;
+
+//
+// make sure we are starting layout text (^P first command)
+//
+	while (*text <= ' ')
+	{
+		text++;
+	}
+	if (*text != '^' || toupper(*(++text)) != 'P')
+	{
+		Quit("PageLayout: Text not headed with ^P");
+	}
+	while (*(text++) != '\n')
+	;
+
+//
+// process text stream
+//
+	do
+	{
+		c = *text;
+		if (c == '^')
+		{
+			HandleCommand();
+		}
+		else if (c <= ' ')
+		{
+			HandleCtrls();
+		}
+		else
+		{
+			HandleWord();
+		}
+	} while (!layoutdone);
+
+	pagenum++;
+
+	if (shownumber)
+	{
+		strcpy(str, "pg ");
+		itoa(pagenum, str2, 10);
+		strcat(str, str2);
+		strcat(str, " of ");
+		itoa(numpages, str2, 10);
+		strcat(str, str2);
+#if GRMODE == CGAGR
+		fontcolor = BLACK^BACKCOLOR;
+#else
+		fontcolor = LIGHTRED^BACKCOLOR;
+#endif
+		py = 186;
+		px = 218;
+		VWB_DrawPropString(str);
+	}
+
+	fontcolor = oldcolor;
+}
+
+//===========================================================================
+
+/*
+=====================
+=
+= BackPage
+=
+= Scans for a previous ^P
+=
+=====================
+*/
+
+void BackPage(void)
+{
+	pagenum--;
+	do
+	{
+		text--;
+		if (text[0] == '^' && toupper(text[1]) == 'P')
+		{
+			return;
+		}
+	} while (1);
+}
+
+//===========================================================================
+
+
+/*
+=====================
+=
+= CacheLayoutGraphics
+=
+= Scans an entire layout file (until a ^E) marking all graphics used, and
+= counting pages, then caches the graphics in
+=
+=====================
+*/
+void CacheLayoutGraphics(void)
+{
+	char	far *bombpoint, far *textstart;
+	char	ch;
+
+	textstart = text;
+	bombpoint = text+30000;
+	numpages = pagenum = 0;
+
+#ifndef KEEN6
+	CA_MarkGrChunk(H_TOPWINDOWPIC);
+	CA_MarkGrChunk(H_LEFTWINDOWPIC);
+	CA_MarkGrChunk(H_RIGHTWINDOWPIC);
+	CA_MarkGrChunk(H_BOTTOMINFOPIC);
+	CA_MarkGrChunk(H_BOTTOMWINDOWPIC);
+#endif
+
+	do
+	{
+		if (*text == '^')
+		{
+			ch = toupper(*(++text));
+			if (ch == 'P')		// start of a page
+			{
+				numpages++;
+			}
+			if (ch == 'E')		// end of file, so load graphics and return
+			{
+				CA_CacheMarks(NULL);
+				text = textstart;
+				return;
+			}
+			if (ch == 'G')		// draw graphic command, so mark graphics
+			{
+				ParsePicCommand();
+				CA_MarkGrChunk(picnum);
+			}
+			if (ch == 'T')		// timed draw graphic command, so mark graphics
+			{
+				ParseTimedCommand();
+				CA_MarkGrChunk(picnum);
+			}
+		}
+		else
+		{
+			text++;
+		}
+
+	} while (text < bombpoint);
+
+	Quit("CacheLayoutGraphics: No ^E to terminate file!");
+}
+
+//===========================================================================
+
+#ifndef KEEN6
+/*
+=================
+=
+= HelpMenu
+=
+=================
+*/
+Sint16 HelpMenu(void)
+{
+	CursorInfo cursor;
+	ControlInfo control;
+	Sint16 ydelta;
+	Uint16 key;
+
+	VWB_Bar(0, 0, 320, 200, BACKCOLOR);
+
+	CA_CacheGrChunk(H_HELPPIC);
+	CA_CacheGrChunk(H_HANDPIC);
+	CA_CacheGrChunk(H_TOPWINDOWPIC);
+	CA_CacheGrChunk(H_LEFTWINDOWPIC);
+	CA_CacheGrChunk(H_RIGHTWINDOWPIC);
+	CA_CacheGrChunk(H_BOTTOMWINDOWPIC);
+
+	VWB_DrawPic(  0,   0, H_TOPWINDOWPIC);
+	VWB_DrawPic(  0,   8, H_LEFTWINDOWPIC);
+	VWB_DrawPic(312,   8, H_RIGHTWINDOWPIC);
+	VWB_DrawPic(  8, 192, H_BOTTOMWINDOWPIC);
+	VWB_DrawPic( 96,   8, H_HELPPIC);
+
+	ydelta = 0;
+	IN_ClearKeysDown();
+	do
+	{
+		if (helpmenupos < 0)
+		{
+			helpmenupos = 0;
+		}
+#ifdef GOODTIMES
+		else if (helpmenupos > 3)
+		{
+			helpmenupos = 3;
+		}
+#else
+		else if (helpmenupos > 4)
+		{
+			helpmenupos = 4;
+		}
+#endif
+		VWB_DrawPic(48, 24*helpmenupos+48, H_HANDPIC);
+		VW_UpdateScreen();
+		VWB_Bar(48, 24*helpmenupos+48, 39, 24, BACKCOLOR);
+		IN_ReadControl(0, &control);
+		IN_ReadCursor(&cursor);
+		if (LastScan)
+		{
+			key = LastScan;
+			IN_ClearKeysDown();
+			switch (key)
+			{
+			case sc_UpArrow:
+				helpmenupos--;
+				break;
+			case sc_DownArrow:
+				helpmenupos++;
+				break;
+			case sc_Enter:
+				VW_ClearVideo(BACKCOLOR);
+				return helpmenupos;
+			case sc_Escape:
+				VW_ClearVideo(BACKCOLOR);
+				return -1;
+			}
+		}
+		ydelta += cursor.y;
+		if (cursor.button0 || cursor.button1 || control.button0 || control.button1)
+		{
+			VW_ClearVideo(BACKCOLOR);
+			return helpmenupos;
+		}
+		if (ydelta < -40)
+		{
+			ydelta += 40;
+			helpmenupos--;
+		}
+		else if (ydelta > 40)
+		{
+			ydelta -= 40;
+			helpmenupos++;
+		}
+	} while (1);
+}
+
+/*
+=================
+=
+= HelpScreens
+=
+=================
+*/
+void HelpScreens(void)
+{
+	static Uint16 layouttable[5] =
+	{
+		T_HELPART,
+		T_CONTRART,
+		T_STORYART,
+#ifndef GOODTIMES
+		T_ORDERART,
+#endif
+		T_IDART
+	};
+
+	Uint16 olddisplayofs, oldbufferofs, oldfontnumber, temp;
+	Sint16 pos;
+	boolean newpage;
+
+	oldfontnumber = fontnumber;
+	olddisplayofs = displayofs;
+	oldbufferofs = bufferofs;
+	fontnumber = 0;
+
+#if GRMODE == EGAGR
+	EGAMAPMASK(15);
+#endif
+
+	CA_UpLevel();
+	CA_SetGrPurge();
+	VW_ClearVideo(BACKCOLOR);
+
+#if GRMODE == EGAGR
+	RF_FixOfs();
+	bufferofs = 0;
+	displayofs = 0x8000;
+	VW_SetScreen(displayofs, 0);
+#endif
+
+#ifdef KEEN5
+	StartMusic(19);
+#endif
+
+	do
+	{
+		pos = HelpMenu();
+
+		VW_ClearVideo(BACKCOLOR);
+
+		if (pos == -1)
+		{
+			CA_DownLevel();
+			IN_ClearKeysDown();
+			bufferofs = oldbufferofs;
+			displayofs = olddisplayofs;
+			fontnumber = oldfontnumber;
+			VW_ClearVideo(BACKCOLOR);
+			RF_FixOfs();
+#ifdef KEEN5
+			StopMusic();	// Note: it's safer to call StopMusic BEFORE CA_DownLevel
+#endif
+			return;
+		}
+
+		pos = layouttable[pos];
+		CA_CacheGrChunk(pos);
+		text = grsegs[pos];
+		CacheLayoutGraphics();
+
+		newpage = true;
+		do
+		{
+			if (newpage)
+			{
+				newpage = false;
+				PageLayout(true);
+#if GRMODE == CGAGR
+				VW_UpdateScreen();
+#else
+				VW_SetScreen(bufferofs, 0);
+				temp = displayofs;
+				displayofs = bufferofs;
+				bufferofs = temp;
+#endif
+			}
+
+			LastScan = 0;
+			while (!LastScan);
+
+			switch (LastScan)
+			{
+			case sc_UpArrow:
+			case sc_LeftArrow:
+			case sc_PgUp:
+				if (pagenum > 1)
+				{
+					BackPage();
+					BackPage();
+					newpage = true;
+				}
+				break;
+			case sc_DownArrow:
+			case sc_RightArrow:
+			case sc_PgDn:
+				if (pagenum < numpages)
+				{
+					newpage = true;
+				}
+				break;
+			}
+		} while (LastScan != sc_Escape);
+
+		MM_FreePtr(&grsegs[pos]);
+		IN_ClearKeysDown();
+	} while (true);
+}
+
+#endif
+
+//===========================================================================
+
+/*
+=================
+=
+= FinaleLayout
+=
+=================
+*/
+void FinaleLayout(void)
+{
+	char _seg *textseg;
+	Sint16 i;
+
+	VW_ClearVideo(BACKCOLOR);
+	RF_FixOfs();
+	CA_UpLevel();
+	CA_SetGrPurge();
+	CA_CacheGrChunk(H_FLASHARROW2PIC);
+	CA_CacheGrChunk(H_FLASHARROW1PIC);
+
+#ifdef KEEN5
+	if (gamestate.leveldone[13] == ex_fusebroke)
+	{
+		CA_CacheGrChunk(T_ENDART2);
+		textseg = grsegs[T_ENDART2];
+	}
+	else
+	{
+		CA_CacheGrChunk(T_ENDART);
+		textseg = grsegs[T_ENDART];
+	}
+#else
+	CA_CacheGrChunk(T_ENDART);
+	textseg = grsegs[T_ENDART];
+#endif
+
+	text = textseg;
+	CacheLayoutGraphics();
+
+	StartMusic(ENDINGMUSIC);
+
+	while (pagenum < numpages)
+	{
+		PageLayout(false);
+		IN_ClearKeysDown();
+#if GRMODE == CGAGR
+		VW_UpdateScreen();
+#else
+		VW_SetScreen(bufferofs, 0);
+#endif
+
+		do
+		{
+			VWB_DrawPic(298, 184, H_FLASHARROW1PIC);
+#if GRMODE == CGAGR
+			VW_UpdateScreen();
+#endif
+			for (i=0; i<TickBase; i++)
+			{
+				if (IN_IsUserInput())
+				{
+					goto nextpage;
+				}
+				VW_WaitVBL(1);
+			}
+
+			VWB_DrawPic(298, 184, H_FLASHARROW2PIC);
+#if GRMODE == CGAGR
+			VW_UpdateScreen();
+#endif
+			for (i=0; i<TickBase; i++)
+			{
+				if (IN_IsUserInput())
+				{
+					goto nextpage;
+				}
+				VW_WaitVBL(1);
+			}
+		} while (1);
+
+nextpage:
+		;	// Borland C++ 2.0 needs a semicolon here...
+	}
+
+	StopMusic();
+
+#ifdef KEEN5
+	if (gamestate.leveldone[13] == ex_fusebroke)
+	{
+		MM_FreePtr(&grsegs[T_ENDART2]);
+	}
+	else
+	{
+		MM_FreePtr(&grsegs[H_FLASHARROW1PIC]);	// BUG! this should free T_ENDART, the arrow should be freed after the else branch!
+	}
+#else
+	MM_FreePtr(&grsegs[T_ENDART]);
+	MM_FreePtr(&grsegs[H_FLASHARROW1PIC]);
+#endif
+	MM_FreePtr(&grsegs[H_FLASHARROW2PIC]);
+	CA_DownLevel();
+	IN_ClearKeysDown();
+#if GRMODE != CGAGR
+	VW_ClearVideo(BACKCOLOR);
+	RF_FixOfs();
+#endif
+	CA_FreeGraphics();
+}
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/COPYING b/16/keen456/KEEN4-6/COPYING
new file mode 100755
index 00000000..d159169d
--- /dev/null
+++ b/16/keen456/KEEN4-6/COPYING
@@ -0,0 +1,339 @@
+                    GNU GENERAL PUBLIC LICENSE
+                       Version 2, June 1991
+
+ Copyright (C) 1989, 1991 Free Software Foundation, Inc.,
+ 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
+ Everyone is permitted to copy and distribute verbatim copies
+ of this license document, but changing it is not allowed.
+
+                            Preamble
+
+  The licenses for most software are designed to take away your
+freedom to share and change it.  By contrast, the GNU General Public
+License is intended to guarantee your freedom to share and change free
+software--to make sure the software is free for all its users.  This
+General Public License applies to most of the Free Software
+Foundation's software and to any other program whose authors commit to
+using it.  (Some other Free Software Foundation software is covered by
+the GNU Lesser General Public License instead.)  You can apply it to
+your programs, too.
+
+  When we speak of free software, we are referring to freedom, not
+price.  Our General Public Licenses are designed to make sure that you
+have the freedom to distribute copies of free software (and charge for
+this service if you wish), that you receive source code or can get it
+if you want it, that you can change the software or use pieces of it
+in new free programs; and that you know you can do these things.
+
+  To protect your rights, we need to make restrictions that forbid
+anyone to deny you these rights or to ask you to surrender the rights.
+These restrictions translate to certain responsibilities for you if you
+distribute copies of the software, or if you modify it.
+
+  For example, if you distribute copies of such a program, whether
+gratis or for a fee, you must give the recipients all the rights that
+you have.  You must make sure that they, too, receive or can get the
+source code.  And you must show them these terms so they know their
+rights.
+
+  We protect your rights with two steps: (1) copyright the software, and
+(2) offer you this license which gives you legal permission to copy,
+distribute and/or modify the software.
+
+  Also, for each author's protection and ours, we want to make certain
+that everyone understands that there is no warranty for this free
+software.  If the software is modified by someone else and passed on, we
+want its recipients to know that what they have is not the original, so
+that any problems introduced by others will not reflect on the original
+authors' reputations.
+
+  Finally, any free program is threatened constantly by software
+patents.  We wish to avoid the danger that redistributors of a free
+program will individually obtain patent licenses, in effect making the
+program proprietary.  To prevent this, we have made it clear that any
+patent must be licensed for everyone's free use or not licensed at all.
+
+  The precise terms and conditions for copying, distribution and
+modification follow.
+
+                    GNU GENERAL PUBLIC LICENSE
+   TERMS AND CONDITIONS FOR COPYING, DISTRIBUTION AND MODIFICATION
+
+  0. This License applies to any program or other work which contains
+a notice placed by the copyright holder saying it may be distributed
+under the terms of this General Public License.  The "Program", below,
+refers to any such program or work, and a "work based on the Program"
+means either the Program or any derivative work under copyright law:
+that is to say, a work containing the Program or a portion of it,
+either verbatim or with modifications and/or translated into another
+language.  (Hereinafter, translation is included without limitation in
+the term "modification".)  Each licensee is addressed as "you".
+
+Activities other than copying, distribution and modification are not
+covered by this License; they are outside its scope.  The act of
+running the Program is not restricted, and the output from the Program
+is covered only if its contents constitute a work based on the
+Program (independent of having been made by running the Program).
+Whether that is true depends on what the Program does.
+
+  1. You may copy and distribute verbatim copies of the Program's
+source code as you receive it, in any medium, provided that you
+conspicuously and appropriately publish on each copy an appropriate
+copyright notice and disclaimer of warranty; keep intact all the
+notices that refer to this License and to the absence of any warranty;
+and give any other recipients of the Program a copy of this License
+along with the Program.
+
+You may charge a fee for the physical act of transferring a copy, and
+you may at your option offer warranty protection in exchange for a fee.
+
+  2. You may modify your copy or copies of the Program or any portion
+of it, thus forming a work based on the Program, and copy and
+distribute such modifications or work under the terms of Section 1
+above, provided that you also meet all of these conditions:
+
+    a) You must cause the modified files to carry prominent notices
+    stating that you changed the files and the date of any change.
+
+    b) You must cause any work that you distribute or publish, that in
+    whole or in part contains or is derived from the Program or any
+    part thereof, to be licensed as a whole at no charge to all third
+    parties under the terms of this License.
+
+    c) If the modified program normally reads commands interactively
+    when run, you must cause it, when started running for such
+    interactive use in the most ordinary way, to print or display an
+    announcement including an appropriate copyright notice and a
+    notice that there is no warranty (or else, saying that you provide
+    a warranty) and that users may redistribute the program under
+    these conditions, and telling the user how to view a copy of this
+    License.  (Exception: if the Program itself is interactive but
+    does not normally print such an announcement, your work based on
+    the Program is not required to print an announcement.)
+
+These requirements apply to the modified work as a whole.  If
+identifiable sections of that work are not derived from the Program,
+and can be reasonably considered independent and separate works in
+themselves, then this License, and its terms, do not apply to those
+sections when you distribute them as separate works.  But when you
+distribute the same sections as part of a whole which is a work based
+on the Program, the distribution of the whole must be on the terms of
+this License, whose permissions for other licensees extend to the
+entire whole, and thus to each and every part regardless of who wrote it.
+
+Thus, it is not the intent of this section to claim rights or contest
+your rights to work written entirely by you; rather, the intent is to
+exercise the right to control the distribution of derivative or
+collective works based on the Program.
+
+In addition, mere aggregation of another work not based on the Program
+with the Program (or with a work based on the Program) on a volume of
+a storage or distribution medium does not bring the other work under
+the scope of this License.
+
+  3. You may copy and distribute the Program (or a work based on it,
+under Section 2) in object code or executable form under the terms of
+Sections 1 and 2 above provided that you also do one of the following:
+
+    a) Accompany it with the complete corresponding machine-readable
+    source code, which must be distributed under the terms of Sections
+    1 and 2 above on a medium customarily used for software interchange; or,
+
+    b) Accompany it with a written offer, valid for at least three
+    years, to give any third party, for a charge no more than your
+    cost of physically performing source distribution, a complete
+    machine-readable copy of the corresponding source code, to be
+    distributed under the terms of Sections 1 and 2 above on a medium
+    customarily used for software interchange; or,
+
+    c) Accompany it with the information you received as to the offer
+    to distribute corresponding source code.  (This alternative is
+    allowed only for noncommercial distribution and only if you
+    received the program in object code or executable form with such
+    an offer, in accord with Subsection b above.)
+
+The source code for a work means the preferred form of the work for
+making modifications to it.  For an executable work, complete source
+code means all the source code for all modules it contains, plus any
+associated interface definition files, plus the scripts used to
+control compilation and installation of the executable.  However, as a
+special exception, the source code distributed need not include
+anything that is normally distributed (in either source or binary
+form) with the major components (compiler, kernel, and so on) of the
+operating system on which the executable runs, unless that component
+itself accompanies the executable.
+
+If distribution of executable or object code is made by offering
+access to copy from a designated place, then offering equivalent
+access to copy the source code from the same place counts as
+distribution of the source code, even though third parties are not
+compelled to copy the source along with the object code.
+
+  4. You may not copy, modify, sublicense, or distribute the Program
+except as expressly provided under this License.  Any attempt
+otherwise to copy, modify, sublicense or distribute the Program is
+void, and will automatically terminate your rights under this License.
+However, parties who have received copies, or rights, from you under
+this License will not have their licenses terminated so long as such
+parties remain in full compliance.
+
+  5. You are not required to accept this License, since you have not
+signed it.  However, nothing else grants you permission to modify or
+distribute the Program or its derivative works.  These actions are
+prohibited by law if you do not accept this License.  Therefore, by
+modifying or distributing the Program (or any work based on the
+Program), you indicate your acceptance of this License to do so, and
+all its terms and conditions for copying, distributing or modifying
+the Program or works based on it.
+
+  6. Each time you redistribute the Program (or any work based on the
+Program), the recipient automatically receives a license from the
+original licensor to copy, distribute or modify the Program subject to
+these terms and conditions.  You may not impose any further
+restrictions on the recipients' exercise of the rights granted herein.
+You are not responsible for enforcing compliance by third parties to
+this License.
+
+  7. If, as a consequence of a court judgment or allegation of patent
+infringement or for any other reason (not limited to patent issues),
+conditions are imposed on you (whether by court order, agreement or
+otherwise) that contradict the conditions of this License, they do not
+excuse you from the conditions of this License.  If you cannot
+distribute so as to satisfy simultaneously your obligations under this
+License and any other pertinent obligations, then as a consequence you
+may not distribute the Program at all.  For example, if a patent
+license would not permit royalty-free redistribution of the Program by
+all those who receive copies directly or indirectly through you, then
+the only way you could satisfy both it and this License would be to
+refrain entirely from distribution of the Program.
+
+If any portion of this section is held invalid or unenforceable under
+any particular circumstance, the balance of the section is intended to
+apply and the section as a whole is intended to apply in other
+circumstances.
+
+It is not the purpose of this section to induce you to infringe any
+patents or other property right claims or to contest validity of any
+such claims; this section has the sole purpose of protecting the
+integrity of the free software distribution system, which is
+implemented by public license practices.  Many people have made
+generous contributions to the wide range of software distributed
+through that system in reliance on consistent application of that
+system; it is up to the author/donor to decide if he or she is willing
+to distribute software through any other system and a licensee cannot
+impose that choice.
+
+This section is intended to make thoroughly clear what is believed to
+be a consequence of the rest of this License.
+
+  8. If the distribution and/or use of the Program is restricted in
+certain countries either by patents or by copyrighted interfaces, the
+original copyright holder who places the Program under this License
+may add an explicit geographical distribution limitation excluding
+those countries, so that distribution is permitted only in or among
+countries not thus excluded.  In such case, this License incorporates
+the limitation as if written in the body of this License.
+
+  9. The Free Software Foundation may publish revised and/or new versions
+of the General Public License from time to time.  Such new versions will
+be similar in spirit to the present version, but may differ in detail to
+address new problems or concerns.
+
+Each version is given a distinguishing version number.  If the Program
+specifies a version number of this License which applies to it and "any
+later version", you have the option of following the terms and conditions
+either of that version or of any later version published by the Free
+Software Foundation.  If the Program does not specify a version number of
+this License, you may choose any version ever published by the Free Software
+Foundation.
+
+  10. If you wish to incorporate parts of the Program into other free
+programs whose distribution conditions are different, write to the author
+to ask for permission.  For software which is copyrighted by the Free
+Software Foundation, write to the Free Software Foundation; we sometimes
+make exceptions for this.  Our decision will be guided by the two goals
+of preserving the free status of all derivatives of our free software and
+of promoting the sharing and reuse of software generally.
+
+                            NO WARRANTY
+
+  11. BECAUSE THE PROGRAM IS LICENSED FREE OF CHARGE, THERE IS NO WARRANTY
+FOR THE PROGRAM, TO THE EXTENT PERMITTED BY APPLICABLE LAW.  EXCEPT WHEN
+OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR OTHER PARTIES
+PROVIDE THE PROGRAM "AS IS" WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESSED
+OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF
+MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE.  THE ENTIRE RISK AS
+TO THE QUALITY AND PERFORMANCE OF THE PROGRAM IS WITH YOU.  SHOULD THE
+PROGRAM PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL NECESSARY SERVICING,
+REPAIR OR CORRECTION.
+
+  12. IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING
+WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MAY MODIFY AND/OR
+REDISTRIBUTE THE PROGRAM AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES,
+INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING
+OUT OF THE USE OR INABILITY TO USE THE PROGRAM (INCLUDING BUT NOT LIMITED
+TO LOSS OF DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY
+YOU OR THIRD PARTIES OR A FAILURE OF THE PROGRAM TO OPERATE WITH ANY OTHER
+PROGRAMS), EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE
+POSSIBILITY OF SUCH DAMAGES.
+
+                     END OF TERMS AND CONDITIONS
+
+            How to Apply These Terms to Your New Programs
+
+  If you develop a new program, and you want it to be of the greatest
+possible use to the public, the best way to achieve this is to make it
+free software which everyone can redistribute and change under these terms.
+
+  To do so, attach the following notices to the program.  It is safest
+to attach them to the start of each source file to most effectively
+convey the exclusion of warranty; and each file should have at least
+the "copyright" line and a pointer to where the full notice is found.
+
+    <one line to give the program's name and a brief idea of what it does.>
+    Copyright (C) <year>  <name of author>
+
+    This program is free software; you can redistribute it and/or modify
+    it under the terms of the GNU General Public License as published by
+    the Free Software Foundation; either version 2 of the License, or
+    (at your option) any later version.
+
+    This program is distributed in the hope that it will be useful,
+    but WITHOUT ANY WARRANTY; without even the implied warranty of
+    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+    GNU General Public License for more details.
+
+    You should have received a copy of the GNU General Public License along
+    with this program; if not, write to the Free Software Foundation, Inc.,
+    51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+
+Also add information on how to contact you by electronic and paper mail.
+
+If the program is interactive, make it output a short notice like this
+when it starts in an interactive mode:
+
+    Gnomovision version 69, Copyright (C) year name of author
+    Gnomovision comes with ABSOLUTELY NO WARRANTY; for details type `show w'.
+    This is free software, and you are welcome to redistribute it
+    under certain conditions; type `show c' for details.
+
+The hypothetical commands `show w' and `show c' should show the appropriate
+parts of the General Public License.  Of course, the commands you use may
+be called something other than `show w' and `show c'; they could even be
+mouse-clicks or menu items--whatever suits your program.
+
+You should also get your employer (if you work as a programmer) or your
+school, if any, to sign a "copyright disclaimer" for the program, if
+necessary.  Here is a sample; alter the names:
+
+  Yoyodyne, Inc., hereby disclaims all copyright interest in the program
+  `Gnomovision' (which makes passes at compilers) written by James Hacker.
+
+  <signature of Ty Coon>, 1 April 1989
+  Ty Coon, President of Vice
+
+This General Public License does not permit incorporating your program into
+proprietary programs.  If your program is a subroutine library, you may
+consider it more useful to permit linking proprietary applications with the
+library.  If this is what you want to do, use the GNU Lesser General
+Public License instead of this License.
diff --git a/16/keen456/KEEN4-6/ID_CA.C b/16/keen456/KEEN4-6/ID_CA.C
new file mode 100755
index 00000000..a8323a21
--- /dev/null
+++ b/16/keen456/KEEN4-6/ID_CA.C
@@ -0,0 +1,2151 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+// ID_CA.C
+
+/*
+=============================================================================
+
+Id Software Caching Manager
+---------------------------
+
+Must be started BEFORE the memory manager, because it needs to get the headers
+loaded into the data segment
+
+=============================================================================
+*/
+
+#include "ID_HEADS.H"
+#pragma hdrstop
+
+#pragma warn -pro
+#pragma warn -use
+
+#define THREEBYTEGRSTARTS
+
+/*
+=============================================================================
+
+						 LOCAL CONSTANTS
+
+=============================================================================
+*/
+
+typedef struct
+{
+  unsigned bit0,bit1;	// 0-255 is a character, > is a pointer to a node
+} huffnode;
+
+
+typedef struct
+{
+	unsigned	RLEWtag;
+	long		headeroffsets[100];
+	byte		tileinfo[];
+} mapfiletype;
+
+
+/*
+=============================================================================
+
+						 GLOBAL VARIABLES
+
+=============================================================================
+*/
+
+byte 		_seg	*tinf;
+int			mapon;
+
+unsigned	_seg	*mapsegs[3];
+maptype		_seg	*mapheaderseg[NUMMAPS];
+byte		_seg	*audiosegs[NUMSNDCHUNKS];
+void		_seg	*grsegs[NUMCHUNKS];
+
+byte		far	grneeded[NUMCHUNKS];
+byte		ca_levelbit,ca_levelnum;
+
+int			profilehandle,debughandle;
+
+void	(*drawcachebox)		(char *title, unsigned numcache);
+void	(*updatecachebox)	(void);
+void	(*finishcachebox)	(void);
+
+/*
+=============================================================================
+
+						 LOCAL VARIABLES
+
+=============================================================================
+*/
+
+extern	long	far	CGAhead;
+extern	long	far	EGAhead;
+extern	byte	CGAdict;
+extern	byte	EGAdict;
+extern	byte	far	maphead;
+extern	byte	mapdict;
+extern	byte	far	audiohead;
+extern	byte	audiodict;
+
+
+long		_seg *grstarts;	// array of offsets in egagraph, -1 for sparse
+long		_seg *audiostarts;	// array of offsets in audio / audiot
+
+#ifdef GRHEADERLINKED
+huffnode	*grhuffman;
+#else
+huffnode	grhuffman[255];
+#endif
+
+#ifdef AUDIOHEADERLINKED
+huffnode	*audiohuffman;
+#else
+huffnode	audiohuffman[255];
+#endif
+
+
+int			grhandle;		// handle to EGAGRAPH
+int			maphandle;		// handle to MAPTEMP / GAMEMAPS
+int			audiohandle;	// handle to AUDIOT / AUDIO
+
+long		chunkcomplen,chunkexplen;
+
+SDMode		oldsoundmode;
+
+
+
+void	CAL_DialogDraw (char *title,unsigned numcache);
+void	CAL_DialogUpdate (void);
+void	CAL_DialogFinish (void);
+void	CAL_CarmackExpand (unsigned far *source, unsigned far *dest,
+		unsigned length);
+
+
+#ifdef THREEBYTEGRSTARTS
+#define FILEPOSSIZE	3
+//#define	GRFILEPOS(c) (*(long far *)(((byte far *)grstarts)+(c)*3)&0xffffff)
+long GRFILEPOS(int c)
+{
+	long value;
+	int	offset;
+
+	offset = c*3;
+
+	value = *(long far *)(((byte far *)grstarts)+offset);
+
+	value &= 0x00ffffffl;
+
+	if (value == 0xffffffl)
+		value = -1;
+
+	return value;
+};
+#else
+#define FILEPOSSIZE	4
+#define	GRFILEPOS(c) (grstarts[c])
+#endif
+
+/*
+=============================================================================
+
+					   LOW LEVEL ROUTINES
+
+=============================================================================
+*/
+
+/*
+============================
+=
+= CA_OpenDebug / CA_CloseDebug
+=
+= Opens a binary file with the handle "debughandle"
+=
+============================
+*/
+
+void CA_OpenDebug (void)
+{
+	unlink ("DEBUG.TXT");
+	debughandle = open("DEBUG.TXT", O_CREAT | O_WRONLY | O_TEXT);
+}
+
+void CA_CloseDebug (void)
+{
+	close (debughandle);
+}
+
+
+
+/*
+============================
+=
+= CAL_GetGrChunkLength
+=
+= Gets the length of an explicit length chunk (not tiles)
+= The file pointer is positioned so the compressed data can be read in next.
+=
+============================
+*/
+
+void CAL_GetGrChunkLength (int chunk)
+{
+	lseek(grhandle,GRFILEPOS(chunk),SEEK_SET);
+	read(grhandle,&chunkexplen,sizeof(chunkexplen));
+	chunkcomplen = GRFILEPOS(chunk+1)-GRFILEPOS(chunk)-4;
+}
+
+
+/*
+==========================
+=
+= CA_FarRead
+=
+= Read from a file to a far pointer
+=
+==========================
+*/
+
+boolean CA_FarRead (int handle, byte far *dest, long length)
+{
+	if (length>0xffffl)
+		Quit ("CA_FarRead doesn't support 64K reads yet!");
+
+asm		push	ds
+asm		mov	bx,[handle]
+asm		mov	cx,[WORD PTR length]
+asm		mov	dx,[WORD PTR dest]
+asm		mov	ds,[WORD PTR dest+2]
+asm		mov	ah,0x3f				// READ w/handle
+asm		int	21h
+asm		pop	ds
+asm		jnc	good
+	errno = _AX;
+	return	false;
+good:
+asm		cmp	ax,[WORD PTR length]
+asm		je	done
+	errno = EINVFMT;			// user manager knows this is bad read
+	return	false;
+done:
+	return	true;
+}
+
+
+/*
+==========================
+=
+= CA_SegWrite
+=
+= Write from a file to a far pointer
+=
+==========================
+*/
+
+boolean CA_FarWrite (int handle, byte far *source, long length)
+{
+	if (length>0xffffl)
+		Quit ("CA_FarWrite doesn't support 64K reads yet!");
+
+asm		push	ds
+asm		mov	bx,[handle]
+asm		mov	cx,[WORD PTR length]
+asm		mov	dx,[WORD PTR source]
+asm		mov	ds,[WORD PTR source+2]
+asm		mov	ah,0x40			// WRITE w/handle
+asm		int	21h
+asm		pop	ds
+asm		jnc	good
+	errno = _AX;
+	return	false;
+good:
+asm		cmp	ax,[WORD PTR length]
+asm		je	done
+	errno = ENOMEM;				// user manager knows this is bad write
+	return	false;
+
+done:
+	return	true;
+}
+
+
+/*
+==========================
+=
+= CA_ReadFile
+=
+= Reads a file into an allready allocated buffer
+=
+==========================
+*/
+
+boolean CA_ReadFile (char *filename, memptr *ptr)
+{
+	int handle;
+	long size;
+
+	if ((handle = open(filename,O_RDONLY | O_BINARY, S_IREAD)) == -1)
+		return false;
+
+	size = filelength (handle);
+	if (!CA_FarRead (handle,*ptr,size))
+	{
+		close (handle);
+		return false;
+	}
+	close (handle);
+	return true;
+}
+
+
+
+/*
+==========================
+=
+= CA_LoadFile
+=
+= Allocate space for and load a file
+=
+==========================
+*/
+
+boolean CA_LoadFile (char *filename, memptr *ptr)
+{
+	int handle;
+	long size;
+
+	if ((handle = open(filename,O_RDONLY | O_BINARY, S_IREAD)) == -1)
+		return false;
+
+	size = filelength (handle);
+	MM_GetPtr (ptr,size);
+	if (!CA_FarRead (handle,*ptr,size))
+	{
+		close (handle);
+		return false;
+	}
+	close (handle);
+	return true;
+}
+
+/*
+============================================================================
+
+		COMPRESSION routines, see JHUFF.C for more
+
+============================================================================
+*/
+
+
+
+/*
+===============
+=
+= CAL_OptimizeNodes
+=
+= Goes through a huffman table and changes the 256-511 node numbers to the
+= actular address of the node.  Must be called before CAL_HuffExpand
+=
+===============
+*/
+
+void CAL_OptimizeNodes (huffnode *table)
+{
+  huffnode *node;
+  int i;
+
+  node = table;
+
+  for (i=0;i<255;i++)
+  {
+	if (node->bit0 >= 256)
+	  node->bit0 = (unsigned)(table+(node->bit0-256));
+	if (node->bit1 >= 256)
+	  node->bit1 = (unsigned)(table+(node->bit1-256));
+	node++;
+  }
+}
+
+
+
+/*
+======================
+=
+= CAL_HuffExpand
+=
+= Length is the length of the EXPANDED data
+=
+======================
+*/
+
+void CAL_HuffExpand (byte huge *source, byte huge *dest,
+  long length,huffnode *hufftable)
+{
+//  unsigned bit,byte,node,code;
+  unsigned sourceseg,sourceoff,destseg,destoff,endoff;
+  huffnode *headptr;
+//  huffnode *nodeon;
+
+  headptr = hufftable+254;	// head node is allways node 254
+
+  source++;	// normalize
+  source--;
+  dest++;
+  dest--;
+
+  sourceseg = FP_SEG(source);
+  sourceoff = FP_OFF(source);
+  destseg = FP_SEG(dest);
+  destoff = FP_OFF(dest);
+  endoff = destoff+length;
+
+//
+// ds:si source
+// es:di dest
+// ss:bx node pointer
+//
+
+	if (length <0xfff0)
+	{
+
+//--------------------------
+// expand less than 64k of data
+//--------------------------
+
+asm mov	bx,[headptr]
+
+asm	mov	si,[sourceoff]
+asm	mov	di,[destoff]
+asm	mov	es,[destseg]
+asm	mov	ds,[sourceseg]
+asm	mov	ax,[endoff]
+
+asm	mov	ch,[si]				// load first byte
+asm	inc	si
+asm	mov	cl,1
+
+expandshort:
+asm	test	ch,cl			// bit set?
+asm	jnz	bit1short
+asm	mov	dx,[ss:bx]			// take bit0 path from node
+asm	shl	cl,1				// advance to next bit position
+asm	jc	newbyteshort
+asm	jnc	sourceupshort
+
+bit1short:
+asm	mov	dx,[ss:bx+2]		// take bit1 path
+asm	shl	cl,1				// advance to next bit position
+asm	jnc	sourceupshort
+
+newbyteshort:
+asm	mov	ch,[si]				// load next byte
+asm	inc	si
+asm	mov	cl,1				// back to first bit
+
+sourceupshort:
+asm	or	dh,dh				// if dx<256 its a byte, else move node
+asm	jz	storebyteshort
+asm	mov	bx,dx				// next node = (huffnode *)code
+asm	jmp	expandshort
+
+storebyteshort:
+asm	mov	[es:di],dl
+asm	inc	di					// write a decopmpressed byte out
+asm	mov	bx,[headptr]		// back to the head node for next bit
+
+asm	cmp	di,ax				// done?
+asm	jne	expandshort
+	}
+	else
+	{
+
+//--------------------------
+// expand more than 64k of data
+//--------------------------
+
+  length--;
+
+asm mov	bx,[headptr]
+asm	mov	cl,1
+
+asm	mov	si,[sourceoff]
+asm	mov	di,[destoff]
+asm	mov	es,[destseg]
+asm	mov	ds,[sourceseg]
+
+asm	lodsb			// load first byte
+
+expand:
+asm	test	al,cl		// bit set?
+asm	jnz	bit1
+asm	mov	dx,[ss:bx]	// take bit0 path from node
+asm	jmp	gotcode
+bit1:
+asm	mov	dx,[ss:bx+2]	// take bit1 path
+
+gotcode:
+asm	shl	cl,1		// advance to next bit position
+asm	jnc	sourceup
+asm	lodsb
+asm	cmp	si,0x10		// normalize ds:si
+asm  	jb	sinorm
+asm	mov	cx,ds
+asm	inc	cx
+asm	mov	ds,cx
+asm	xor	si,si
+sinorm:
+asm	mov	cl,1		// back to first bit
+
+sourceup:
+asm	or	dh,dh		// if dx<256 its a byte, else move node
+asm	jz	storebyte
+asm	mov	bx,dx		// next node = (huffnode *)code
+asm	jmp	expand
+
+storebyte:
+asm	mov	[es:di],dl
+asm	inc	di		// write a decopmpressed byte out
+asm	mov	bx,[headptr]	// back to the head node for next bit
+
+asm	cmp	di,0x10		// normalize es:di
+asm  	jb	dinorm
+asm	mov	dx,es
+asm	inc	dx
+asm	mov	es,dx
+asm	xor	di,di
+dinorm:
+
+asm	sub	[WORD PTR ss:length],1
+asm	jnc	expand
+asm  	dec	[WORD PTR ss:length+2]
+asm	jns	expand		// when length = ffff ffff, done
+
+	}
+
+asm	mov	ax,ss
+asm	mov	ds,ax
+
+}
+
+
+/*
+======================
+=
+= CAL_CarmackExpand
+=
+= Length is the length of the EXPANDED data
+=
+======================
+*/
+
+#define NEARTAG	0xa7
+#define FARTAG	0xa8
+
+void CAL_CarmackExpand (unsigned far *source, unsigned far *dest, unsigned length)
+{
+	unsigned	ch,chhigh,count,offset;
+	unsigned	far *copyptr, far *inptr, far *outptr;
+
+	length/=2;
+
+	inptr = source;
+	outptr = dest;
+
+	while (length)
+	{
+		ch = *inptr++;
+		chhigh = ch>>8;
+		if (chhigh == NEARTAG)
+		{
+			count = ch&0xff;
+			if (!count)
+			{				// have to insert a word containing the tag byte
+				ch |= *((unsigned char far *)inptr)++;
+				*outptr++ = ch;
+				length--;
+			}
+			else
+			{
+				offset = *((unsigned char far *)inptr)++;
+				copyptr = outptr - offset;
+				length -= count;
+				while (count--)
+					*outptr++ = *copyptr++;
+			}
+		}
+		else if (chhigh == FARTAG)
+		{
+			count = ch&0xff;
+			if (!count)
+			{				// have to insert a word containing the tag byte
+				ch |= *((unsigned char far *)inptr)++;
+				*outptr++ = ch;
+				length --;
+			}
+			else
+			{
+				offset = *inptr++;
+				copyptr = dest + offset;
+				length -= count;
+				while (count--)
+					*outptr++ = *copyptr++;
+			}
+		}
+		else
+		{
+			*outptr++ = ch;
+			length --;
+		}
+	}
+}
+
+
+
+/*
+======================
+=
+= CA_RLEWcompress
+=
+======================
+*/
+
+long CA_RLEWCompress (unsigned huge *source, long length, unsigned huge *dest,
+  unsigned rlewtag)
+{
+  long complength;
+  unsigned value,count,i;
+  unsigned huge *start,huge *end;
+
+  start = dest;
+
+  end = source + (length+1)/2;
+
+//
+// compress it
+//
+  do
+  {
+	count = 1;
+	value = *source++;
+	while (*source == value && source<end)
+	{
+	  count++;
+	  source++;
+	}
+	if (count>3 || value == rlewtag)
+	{
+    //
+    // send a tag / count / value string
+    //
+      *dest++ = rlewtag;
+      *dest++ = count;
+      *dest++ = value;
+    }
+    else
+    {
+    //
+    // send word without compressing
+    //
+      for (i=1;i<=count;i++)
+	*dest++ = value;
+	}
+
+  } while (source<end);
+
+  complength = 2*(dest-start);
+  return complength;
+}
+
+
+/*
+======================
+=
+= CA_RLEWexpand
+= length is EXPANDED length
+=
+======================
+*/
+
+void CA_RLEWexpand (unsigned huge *source, unsigned huge *dest,long length,
+  unsigned rlewtag)
+{
+//  unsigned value,count,i;
+  unsigned huge *end;
+  unsigned sourceseg,sourceoff,destseg,destoff,endseg,endoff;
+
+
+//
+// expand it
+//
+#if 0
+  do
+  {
+	value = *source++;
+	if (value != rlewtag)
+	//
+	// uncompressed
+	//
+	  *dest++=value;
+	else
+	{
+	//
+	// compressed string
+	//
+	  count = *source++;
+	  value = *source++;
+	  for (i=1;i<=count;i++)
+	*dest++ = value;
+	}
+  } while (dest<end);
+#endif
+
+  end = dest + (length)/2;
+  sourceseg = FP_SEG(source);
+  sourceoff = FP_OFF(source);
+  destseg = FP_SEG(dest);
+  destoff = FP_OFF(dest);
+  endseg = FP_SEG(end);
+  endoff = FP_OFF(end);
+
+
+//
+// ax = source value
+// bx = tag value
+// cx = repeat counts
+// dx = scratch
+//
+// NOTE: A repeat count that produces 0xfff0 bytes can blow this!
+//
+
+asm	mov	bx,rlewtag
+asm	mov	si,sourceoff
+asm	mov	di,destoff
+asm	mov	es,destseg
+asm	mov	ds,sourceseg
+
+expand:
+asm	lodsw
+asm	cmp	ax,bx
+asm	je	repeat
+asm	stosw
+asm	jmp	next
+
+repeat:
+asm	lodsw
+asm	mov	cx,ax		// repeat count
+asm	lodsw			// repeat value
+asm	rep stosw
+
+next:
+
+asm	cmp	si,0x10		// normalize ds:si
+asm  	jb	sinorm
+asm	mov	ax,si
+asm	shr	ax,1
+asm	shr	ax,1
+asm	shr	ax,1
+asm	shr	ax,1
+asm	mov	dx,ds
+asm	add	dx,ax
+asm	mov	ds,dx
+asm	and	si,0xf
+sinorm:
+asm	cmp	di,0x10		// normalize es:di
+asm  	jb	dinorm
+asm	mov	ax,di
+asm	shr	ax,1
+asm	shr	ax,1
+asm	shr	ax,1
+asm	shr	ax,1
+asm	mov	dx,es
+asm	add	dx,ax
+asm	mov	es,dx
+asm	and	di,0xf
+dinorm:
+
+asm	cmp     di,ss:endoff
+asm	jne	expand
+asm	mov	ax,es
+asm	cmp	ax,ss:endseg
+asm	jb	expand
+
+asm	mov	ax,ss
+asm	mov	ds,ax
+
+}
+
+
+
+/*
+=============================================================================
+
+					 CACHE MANAGER ROUTINES
+
+=============================================================================
+*/
+
+
+/*
+======================
+=
+= CAL_SetupGrFile
+=
+======================
+*/
+
+void CAL_SetupGrFile (void)
+{
+	int handle;
+	memptr compseg;
+
+#ifdef GRHEADERLINKED
+
+#if GRMODE == EGAGR
+	grhuffman = (huffnode *)&EGAdict;
+	grstarts = (long _seg *)FP_SEG(&EGAhead);
+#endif
+#if GRMODE == CGAGR
+	grhuffman = (huffnode *)&CGAdict;
+	grstarts = (long _seg *)FP_SEG(&CGAhead);
+#endif
+
+	CAL_OptimizeNodes (grhuffman);
+
+#else
+
+//
+// load ???dict.ext (huffman dictionary for graphics files)
+//
+
+	if ((handle = open(GREXT"DICT."EXTENSION,
+		 O_RDONLY | O_BINARY, S_IREAD)) == -1)
+		Quit ("Can't open "GREXT"DICT."EXTENSION"!");
+
+	read(handle, &grhuffman, sizeof(grhuffman));
+	close(handle);
+	CAL_OptimizeNodes (grhuffman);
+//
+// load the data offsets from ???head.ext
+//
+	MM_GetPtr (&(memptr)grstarts,(NUMCHUNKS+1)*FILEPOSSIZE);
+
+	if ((handle = open(GREXT"HEAD."EXTENSION,
+		 O_RDONLY | O_BINARY, S_IREAD)) == -1)
+		Quit ("Can't open "GREXT"HEAD."EXTENSION"!");
+
+	CA_FarRead(handle, (memptr)grstarts, (NUMCHUNKS+1)*FILEPOSSIZE);
+
+	close(handle);
+
+
+#endif
+
+//
+// Open the graphics file, leaving it open until the game is finished
+//
+	grhandle = open(GREXT"GRAPH."EXTENSION, O_RDONLY | O_BINARY);
+	if (grhandle == -1)
+		Quit ("Cannot open "GREXT"GRAPH."EXTENSION"!");
+
+
+//
+// load the pic and sprite headers into the arrays in the data segment
+//
+#if NUMPICS>0
+	MM_GetPtr(&(memptr)pictable,NUMPICS*sizeof(pictabletype));
+	CAL_GetGrChunkLength(STRUCTPIC);		// position file pointer
+	MM_GetPtr(&compseg,chunkcomplen);
+	CA_FarRead (grhandle,compseg,chunkcomplen);
+	CAL_HuffExpand (compseg, (byte huge *)pictable,NUMPICS*sizeof(pictabletype),grhuffman);
+	MM_FreePtr(&compseg);
+#endif
+
+#if NUMPICM>0
+	MM_GetPtr(&(memptr)picmtable,NUMPICM*sizeof(pictabletype));
+	CAL_GetGrChunkLength(STRUCTPICM);		// position file pointer
+	MM_GetPtr(&compseg,chunkcomplen);
+	CA_FarRead (grhandle,compseg,chunkcomplen);
+	CAL_HuffExpand (compseg, (byte huge *)picmtable,NUMPICS*sizeof(pictabletype),grhuffman);
+	MM_FreePtr(&compseg);
+#endif
+
+#if NUMSPRITES>0
+	MM_GetPtr(&(memptr)spritetable,NUMSPRITES*sizeof(spritetabletype));
+	CAL_GetGrChunkLength(STRUCTSPRITE);	// position file pointer
+	MM_GetPtr(&compseg,chunkcomplen);
+	CA_FarRead (grhandle,compseg,chunkcomplen);
+	CAL_HuffExpand (compseg, (byte huge *)spritetable,NUMSPRITES*sizeof(spritetabletype),grhuffman);
+	MM_FreePtr(&compseg);
+#endif
+
+}
+
+//==========================================================================
+
+
+/*
+======================
+=
+= CAL_SetupMapFile
+=
+======================
+*/
+
+void CAL_SetupMapFile (void)
+{
+	int handle;
+	long length;
+
+//
+// load maphead.ext (offsets and tileinfo for map file)
+//
+#ifndef MAPHEADERLINKED
+	if ((handle = open("MAPHEAD."EXTENSION,
+		 O_RDONLY | O_BINARY, S_IREAD)) == -1)
+		Quit ("Can't open MAPHEAD."EXTENSION"!");
+	length = filelength(handle);
+	MM_GetPtr (&(memptr)tinf,length);
+	CA_FarRead(handle, tinf, length);
+	close(handle);
+#else
+
+	tinf = (byte _seg *)FP_SEG(&maphead);
+
+#endif
+
+//
+// open the data file
+//
+#ifdef MAPHEADERLINKED
+	if ((maphandle = open("GAMEMAPS."EXTENSION,
+		 O_RDONLY | O_BINARY, S_IREAD)) == -1)
+		Quit ("Can't open GAMEMAPS."EXTENSION"!");
+#else
+	if ((maphandle = open("MAPTEMP."EXTENSION,
+		 O_RDONLY | O_BINARY, S_IREAD)) == -1)
+		Quit ("Can't open MAPTEMP."EXTENSION"!");
+#endif
+}
+
+//==========================================================================
+
+
+/*
+======================
+=
+= CAL_SetupAudioFile
+=
+======================
+*/
+
+void CAL_SetupAudioFile (void)
+{
+	int handle;
+	long length;
+
+//
+// load maphead.ext (offsets and tileinfo for map file)
+//
+#ifndef AUDIOHEADERLINKED
+	if ((handle = open("AUDIOHED."EXTENSION,
+		 O_RDONLY | O_BINARY, S_IREAD)) == -1)
+		Quit ("Can't open AUDIOHED."EXTENSION"!");
+	length = filelength(handle);
+	MM_GetPtr (&(memptr)audiostarts,length);
+	CA_FarRead(handle, (byte far *)audiostarts, length);
+	close(handle);
+#else
+	audiohuffman = (huffnode *)&audiodict;
+	CAL_OptimizeNodes (audiohuffman);
+	audiostarts = (long _seg *)FP_SEG(&audiohead);
+#endif
+
+//
+// open the data file
+//
+#ifndef AUDIOHEADERLINKED
+	if ((audiohandle = open("AUDIOT."EXTENSION,
+		 O_RDONLY | O_BINARY, S_IREAD)) == -1)
+		Quit ("Can't open AUDIOT."EXTENSION"!");
+#else
+	if ((audiohandle = open("AUDIO."EXTENSION,
+		 O_RDONLY | O_BINARY, S_IREAD)) == -1)
+		Quit ("Can't open AUDIO."EXTENSION"!");
+#endif
+}
+
+//==========================================================================
+
+
+/*
+======================
+=
+= CA_Startup
+=
+= Open all files and load in headers
+=
+======================
+*/
+
+void CA_Startup (void)
+{
+#ifdef PROFILE
+	unlink ("PROFILE.TXT");
+	profilehandle = open("PROFILE.TXT", O_CREAT | O_WRONLY | O_TEXT);
+#endif
+
+#ifndef NOMAPS
+	CAL_SetupMapFile ();
+#endif
+#ifndef NOGRAPHICS
+	CAL_SetupGrFile ();
+#endif
+#ifndef NOAUDIO
+	CAL_SetupAudioFile ();
+#endif
+
+	mapon = -1;
+	ca_levelbit = 1;
+	ca_levelnum = 0;
+
+	drawcachebox	= CAL_DialogDraw;
+	updatecachebox  = CAL_DialogUpdate;
+	finishcachebox	= CAL_DialogFinish;
+}
+
+//==========================================================================
+
+
+/*
+======================
+=
+= CA_Shutdown
+=
+= Closes all files
+=
+======================
+*/
+
+void CA_Shutdown (void)
+{
+#ifdef PROFILE
+	close (profilehandle);
+#endif
+
+	close (maphandle);
+	close (grhandle);
+	close (audiohandle);
+}
+
+//===========================================================================
+
+/*
+======================
+=
+= CA_CacheAudioChunk
+=
+======================
+*/
+
+void CA_CacheAudioChunk (int chunk)
+{
+	long	pos,compressed;
+#ifdef AUDIOHEADERLINKED
+	long	expanded;
+	memptr	bigbufferseg;
+	byte	far *source;
+#endif
+
+	if (audiosegs[chunk])
+	{
+		MM_SetPurge (&(memptr)audiosegs[chunk],0);
+		return;							// allready in memory
+	}
+
+//
+// load the chunk into a buffer, either the miscbuffer if it fits, or allocate
+// a larger buffer
+//
+	pos = audiostarts[chunk];
+	compressed = audiostarts[chunk+1]-pos;
+
+	lseek(audiohandle,pos,SEEK_SET);
+
+#ifndef AUDIOHEADERLINKED
+
+	MM_GetPtr (&(memptr)audiosegs[chunk],compressed);
+	if (mmerror)
+		return;
+
+	CA_FarRead(audiohandle,audiosegs[chunk],compressed);
+
+#else
+
+	if (compressed<=BUFFERSIZE)
+	{
+		CA_FarRead(audiohandle,bufferseg,compressed);
+		source = bufferseg;
+	}
+	else
+	{
+		MM_GetPtr(&bigbufferseg,compressed);
+		if (mmerror)
+			return;
+		MM_SetLock (&bigbufferseg,true);
+		CA_FarRead(audiohandle,bigbufferseg,compressed);
+		source = bigbufferseg;
+	}
+
+	expanded = *(long far *)source;
+	source += 4;			// skip over length
+	MM_GetPtr (&(memptr)audiosegs[chunk],expanded);
+	if (mmerror)
+		goto done;
+	CAL_HuffExpand (source,audiosegs[chunk],expanded,audiohuffman);
+
+done:
+	if (compressed>BUFFERSIZE)
+		MM_FreePtr(&bigbufferseg);
+#endif
+}
+
+//===========================================================================
+
+/*
+======================
+=
+= CA_LoadAllSounds
+=
+= Purges all sounds, then loads all new ones (mode switch)
+=
+======================
+*/
+
+void CA_LoadAllSounds (void)
+{
+	unsigned	start,i;
+
+	switch (oldsoundmode)
+	{
+	case sdm_Off:
+		goto cachein;
+	case sdm_PC:
+		start = STARTPCSOUNDS;
+		break;
+	case sdm_AdLib:
+		start = STARTADLIBSOUNDS;
+		break;
+	}
+
+	for (i=0;i<NUMSOUNDS;i++,start++)
+		if (audiosegs[start])
+			MM_SetPurge (&(memptr)audiosegs[start],3);		// make purgable
+
+cachein:
+
+	switch (SoundMode)
+	{
+	case sdm_Off:
+		return;
+	case sdm_PC:
+		start = STARTPCSOUNDS;
+		break;
+	case sdm_AdLib:
+		start = STARTADLIBSOUNDS;
+		break;
+	}
+
+	for (i=0;i<NUMSOUNDS;i++,start++)
+		CA_CacheAudioChunk (start);
+
+	oldsoundmode = SoundMode;
+}
+
+//===========================================================================
+
+#if GRMODE == EGAGR
+
+/*
+======================
+=
+= CAL_ShiftSprite
+=
+= Make a shifted (one byte wider) copy of a sprite into another area
+=
+======================
+*/
+
+unsigned	static	sheight,swidth;
+
+void CAL_ShiftSprite (unsigned segment,unsigned source,unsigned dest,
+	unsigned width, unsigned height, unsigned pixshift)
+{
+
+	sheight = height;		// because we are going to reassign bp
+	swidth = width;
+
+asm	mov	ax,[segment]
+asm	mov	ds,ax		// source and dest are in same segment, and all local
+
+asm	mov	bx,[source]
+asm	mov	di,[dest]
+
+asm	mov	bp,[pixshift]
+asm	shl	bp,1
+asm	mov	bp,WORD PTR [shifttabletable+bp]	// bp holds pointer to shift table
+
+//
+// table shift the mask
+//
+asm	mov	dx,[ss:sheight]
+
+domaskrow:
+
+asm	mov	BYTE PTR [di],255	// 0xff first byte
+asm	mov	cx,ss:[swidth]
+
+domaskbyte:
+
+asm	mov	al,[bx]				// source
+asm	not	al
+asm	inc	bx					// next source byte
+asm	xor	ah,ah
+asm	shl	ax,1
+asm	mov	si,ax
+asm	mov	ax,[bp+si]			// table shift into two bytes
+asm	not	ax
+asm	and	[di],al				// and with first byte
+asm	inc	di
+asm	mov	[di],ah				// replace next byte
+
+asm	loop	domaskbyte
+
+asm	inc	di					// the last shifted byte has 1s in it
+asm	dec	dx
+asm	jnz	domaskrow
+
+//
+// table shift the data
+//
+asm	mov	dx,ss:[sheight]
+asm	shl	dx,1
+asm	shl	dx,1				// four planes of data
+
+dodatarow:
+
+asm	mov	BYTE PTR [di],0		// 0 first byte
+asm	mov	cx,ss:[swidth]
+
+dodatabyte:
+
+asm	mov	al,[bx]				// source
+asm	inc	bx					// next source byte
+asm	xor	ah,ah
+asm	shl	ax,1
+asm	mov	si,ax
+asm	mov	ax,[bp+si]			// table shift into two bytes
+asm	or	[di],al				// or with first byte
+asm	inc	di
+asm	mov	[di],ah				// replace next byte
+
+asm	loop	dodatabyte
+
+asm	inc	di					// the last shifted byte has 0s in it
+asm	dec	dx
+asm	jnz	dodatarow
+
+//
+// done
+//
+
+asm	mov	ax,ss				// restore data segment
+asm	mov	ds,ax
+
+}
+
+#endif
+
+//===========================================================================
+
+/*
+======================
+=
+= CAL_CacheSprite
+=
+= Generate shifts and set up sprite structure for a given sprite
+=
+======================
+*/
+
+void CAL_CacheSprite (int chunk, byte far *compressed)
+{
+	int i;
+	unsigned shiftstarts[5];
+	unsigned smallplane,bigplane,expanded;
+	spritetabletype far *spr;
+	spritetype _seg *dest;
+
+#if GRMODE == CGAGR
+//
+// CGA has no pel panning, so shifts are never needed
+//
+	spr = &spritetable[chunk-STARTSPRITES];
+	smallplane = spr->width*spr->height;
+	MM_GetPtr (&grsegs[chunk],smallplane*2+MAXSHIFTS*6);
+	if (mmerror)
+		return;
+	dest = (spritetype _seg *)grsegs[chunk];
+	dest->sourceoffset[0] = MAXSHIFTS*6;	// start data after 3 unsigned tables
+	dest->planesize[0] = smallplane;
+	dest->width[0] = spr->width;
+
+//
+// expand the unshifted shape
+//
+	CAL_HuffExpand (compressed, &dest->data[0],smallplane*2,grhuffman);
+
+#endif
+
+
+#if GRMODE == EGAGR
+
+//
+// calculate sizes
+//
+	spr = &spritetable[chunk-STARTSPRITES];
+	smallplane = spr->width*spr->height;
+	bigplane = (spr->width+1)*spr->height;
+
+	shiftstarts[0] = MAXSHIFTS*6;	// start data after 3 unsigned tables
+	shiftstarts[1] = shiftstarts[0] + smallplane*5;	// 5 planes in a sprite
+	shiftstarts[2] = shiftstarts[1] + bigplane*5;
+	shiftstarts[3] = shiftstarts[2] + bigplane*5;
+	shiftstarts[4] = shiftstarts[3] + bigplane*5;	// nothing ever put here
+
+	expanded = shiftstarts[spr->shifts];
+	MM_GetPtr (&grsegs[chunk],expanded);
+	if (mmerror)
+		return;
+	dest = (spritetype _seg *)grsegs[chunk];
+
+//
+// expand the unshifted shape
+//
+	CAL_HuffExpand (compressed, &dest->data[0],smallplane*5,grhuffman);
+
+//
+// make the shifts!
+//
+	switch (spr->shifts)
+	{
+	case	1:
+		for (i=0;i<4;i++)
+		{
+			dest->sourceoffset[i] = shiftstarts[0];
+			dest->planesize[i] = smallplane;
+			dest->width[i] = spr->width;
+		}
+		break;
+
+	case	2:
+		for (i=0;i<2;i++)
+		{
+			dest->sourceoffset[i] = shiftstarts[0];
+			dest->planesize[i] = smallplane;
+			dest->width[i] = spr->width;
+		}
+		for (i=2;i<4;i++)
+		{
+			dest->sourceoffset[i] = shiftstarts[1];
+			dest->planesize[i] = bigplane;
+			dest->width[i] = spr->width+1;
+		}
+		CAL_ShiftSprite ((unsigned)grsegs[chunk],dest->sourceoffset[0],
+			dest->sourceoffset[2],spr->width,spr->height,4);
+		break;
+
+	case	4:
+		dest->sourceoffset[0] = shiftstarts[0];
+		dest->planesize[0] = smallplane;
+		dest->width[0] = spr->width;
+
+		dest->sourceoffset[1] = shiftstarts[1];
+		dest->planesize[1] = bigplane;
+		dest->width[1] = spr->width+1;
+		CAL_ShiftSprite ((unsigned)grsegs[chunk],dest->sourceoffset[0],
+			dest->sourceoffset[1],spr->width,spr->height,2);
+
+		dest->sourceoffset[2] = shiftstarts[2];
+		dest->planesize[2] = bigplane;
+		dest->width[2] = spr->width+1;
+		CAL_ShiftSprite ((unsigned)grsegs[chunk],dest->sourceoffset[0],
+			dest->sourceoffset[2],spr->width,spr->height,4);
+
+		dest->sourceoffset[3] = shiftstarts[3];
+		dest->planesize[3] = bigplane;
+		dest->width[3] = spr->width+1;
+		CAL_ShiftSprite ((unsigned)grsegs[chunk],dest->sourceoffset[0],
+			dest->sourceoffset[3],spr->width,spr->height,6);
+
+		break;
+
+	default:
+		Quit ("CAL_CacheSprite: Bad shifts number!");
+	}
+
+#endif
+}
+
+//===========================================================================
+
+
+/*
+======================
+=
+= CAL_ExpandGrChunk
+=
+= Does whatever is needed with a pointer to a compressed chunk
+=
+======================
+*/
+
+void CAL_ExpandGrChunk (int chunk, byte far *source)
+{
+	long	expanded;
+
+
+	if (chunk >= STARTTILE8 && chunk < STARTEXTERNS)
+	{
+	//
+	// expanded sizes of tile8/16/32 are implicit
+	//
+
+#if GRMODE == EGAGR
+#define BLOCK		32
+#define MASKBLOCK	40
+#endif
+
+#if GRMODE == CGAGR
+#define BLOCK		16
+#define MASKBLOCK	32
+#endif
+
+		if (chunk<STARTTILE8M)			// tile 8s are all in one chunk!
+			expanded = BLOCK*NUMTILE8;
+		else if (chunk<STARTTILE16)
+			expanded = MASKBLOCK*NUMTILE8M;
+		else if (chunk<STARTTILE16M)	// all other tiles are one/chunk
+			expanded = BLOCK*4;
+		else if (chunk<STARTTILE32)
+			expanded = MASKBLOCK*4;
+		else if (chunk<STARTTILE32M)
+			expanded = BLOCK*16;
+		else
+			expanded = MASKBLOCK*16;
+	}
+	else
+	{
+	//
+	// everything else has an explicit size longword
+	//
+		expanded = *(long far *)source;
+		source += 4;			// skip over length
+	}
+
+//
+// allocate final space, decompress it, and free bigbuffer
+// Sprites need to have shifts made and various other junk
+//
+	if (chunk>=STARTSPRITES && chunk< STARTTILE8)
+		CAL_CacheSprite(chunk,source);
+	else
+	{
+		MM_GetPtr (&grsegs[chunk],expanded);
+		if (mmerror)
+			return;
+		CAL_HuffExpand (source,grsegs[chunk],expanded,grhuffman);
+	}
+}
+
+
+/*
+======================
+=
+= CAL_ReadGrChunk
+=
+= Gets a chunk off disk, optimizing reads to general buffer
+=
+======================
+*/
+
+void CAL_ReadGrChunk (int chunk)
+{
+	long	pos,compressed;
+	memptr	bigbufferseg;
+	byte	far *source;
+	int		next;
+
+//
+// load the chunk into a buffer, either the miscbuffer if it fits, or allocate
+// a larger buffer
+//
+	pos = GRFILEPOS(chunk);
+	if (pos<0)							// $FFFFFFFF start is a sparse tile
+	  return;
+
+	next = chunk +1;
+	while (GRFILEPOS(next) == -1)		// skip past any sparse tiles
+		next++;
+
+	compressed = GRFILEPOS(next)-pos;
+
+	lseek(grhandle,pos,SEEK_SET);
+
+	if (compressed<=BUFFERSIZE)
+	{
+		CA_FarRead(grhandle,bufferseg,compressed);
+		source = bufferseg;
+	}
+	else
+	{
+		MM_GetPtr(&bigbufferseg,compressed);
+		if (mmerror)
+			return;
+		MM_SetLock (&bigbufferseg,true);
+		CA_FarRead(grhandle,bigbufferseg,compressed);
+		source = bigbufferseg;
+	}
+
+	CAL_ExpandGrChunk (chunk,source);
+
+	if (compressed>BUFFERSIZE)
+		MM_FreePtr(&bigbufferseg);
+}
+
+
+/*
+======================
+=
+= CA_CacheGrChunk
+=
+= Makes sure a given chunk is in memory, loadiing it if needed
+=
+======================
+*/
+
+void CA_CacheGrChunk (int chunk)
+{
+	long	pos,compressed;
+	memptr	bigbufferseg;
+	byte	far *source;
+	int		next;
+
+	grneeded[chunk] |= ca_levelbit;		// make sure it doesn't get removed
+	if (grsegs[chunk])
+	{
+		MM_SetPurge (&grsegs[chunk],0);
+		return;							// allready in memory
+	}
+
+//
+// load the chunk into a buffer, either the miscbuffer if it fits, or allocate
+// a larger buffer
+//
+	pos = GRFILEPOS(chunk);
+	if (pos<0)							// $FFFFFFFF start is a sparse tile
+	  return;
+
+	next = chunk +1;
+	while (GRFILEPOS(next) == -1)		// skip past any sparse tiles
+		next++;
+
+	compressed = GRFILEPOS(next)-pos;
+
+	lseek(grhandle,pos,SEEK_SET);
+
+	if (compressed<=BUFFERSIZE)
+	{
+		CA_FarRead(grhandle,bufferseg,compressed);
+		source = bufferseg;
+	}
+	else
+	{
+		MM_GetPtr(&bigbufferseg,compressed);
+		MM_SetLock (&bigbufferseg,true);
+		CA_FarRead(grhandle,bigbufferseg,compressed);
+		source = bigbufferseg;
+	}
+
+	CAL_ExpandGrChunk (chunk,source);
+
+	if (compressed>BUFFERSIZE)
+		MM_FreePtr(&bigbufferseg);
+}
+
+
+
+//==========================================================================
+
+/*
+======================
+=
+= CA_CacheMap
+=
+======================
+*/
+
+void CA_CacheMap (int mapnum)
+{
+	long	pos,compressed;
+	int		plane;
+	memptr	*dest,bigbufferseg;
+	unsigned	size;
+	unsigned	far	*source;
+#ifdef MAPHEADERLINKED
+	memptr	buffer2seg;
+	long	expanded;
+#endif
+
+
+//
+// free up memory from last map
+//
+	if (mapon>-1 && mapheaderseg[mapon])
+		MM_SetPurge (&(memptr)mapheaderseg[mapon],3);
+	for (plane=0;plane<MAPPLANES;plane++)
+		if (mapsegs[plane])
+			MM_FreePtr (&(memptr)mapsegs[plane]);
+
+	mapon = mapnum;
+
+
+//
+// load map header
+// The header will be cached if it is still around
+//
+	if (!mapheaderseg[mapnum])
+	{
+		pos = ((mapfiletype	_seg *)tinf)->headeroffsets[mapnum];
+		if (pos<0)						// $FFFFFFFF start is a sparse map
+		  Quit ("CA_CacheMap: Tried to load a non existent map!");
+
+		MM_GetPtr(&(memptr)mapheaderseg[mapnum],sizeof(maptype));
+		lseek(maphandle,pos,SEEK_SET);
+		CA_FarRead (maphandle,(memptr)mapheaderseg[mapnum],sizeof(maptype));
+	}
+	else
+		MM_SetPurge (&(memptr)mapheaderseg[mapnum],0);
+
+//
+// load the planes in
+// If a plane's pointer still exists it will be overwritten (levels are
+// allways reloaded, never cached)
+//
+
+	size = mapheaderseg[mapnum]->width * mapheaderseg[mapnum]->height * 2;
+
+	for (plane = 0; plane<MAPPLANES; plane++)
+	{
+		pos = mapheaderseg[mapnum]->planestart[plane];
+		compressed = mapheaderseg[mapnum]->planelength[plane];
+
+		if (!compressed)
+			continue;		// the plane is not used in this game
+
+		dest = &(memptr)mapsegs[plane];
+		MM_GetPtr(dest,size);
+
+		lseek(maphandle,pos,SEEK_SET);
+		if (compressed<=BUFFERSIZE)
+			source = bufferseg;
+		else
+		{
+			MM_GetPtr(&bigbufferseg,compressed);
+			MM_SetLock (&bigbufferseg,true);
+			source = bigbufferseg;
+		}
+
+		CA_FarRead(maphandle,(byte far *)source,compressed);
+#ifdef MAPHEADERLINKED
+		//
+		// unhuffman, then unRLEW
+		// The huffman'd chunk has a two byte expanded length first
+		// The resulting RLEW chunk also does, even though it's not really
+		// needed
+		//
+		expanded = *source;
+		source++;
+		MM_GetPtr (&buffer2seg,expanded);
+		CAL_CarmackExpand (source, (unsigned far *)buffer2seg,expanded);
+		CA_RLEWexpand (((unsigned far *)buffer2seg)+1,*dest,size,
+		((mapfiletype _seg *)tinf)->RLEWtag);
+		MM_FreePtr (&buffer2seg);
+
+#else
+		//
+		// unRLEW, skipping expanded length
+		//
+		CA_RLEWexpand (source+1, *dest,size,
+		((mapfiletype _seg *)tinf)->RLEWtag);
+#endif
+
+		if (compressed>BUFFERSIZE)
+			MM_FreePtr(&bigbufferseg);
+	}
+}
+
+//===========================================================================
+
+/*
+======================
+=
+= CA_UpLevel
+=
+= Goes up a bit level in the needed lists and clears it out.
+= Everything is made purgable
+=
+======================
+*/
+
+void CA_UpLevel (void)
+{
+	if (ca_levelnum==7)
+		Quit ("CA_UpLevel: Up past level 7!");
+
+	ca_levelbit<<=1;
+	ca_levelnum++;
+}
+
+//===========================================================================
+
+/*
+======================
+=
+= CA_DownLevel
+=
+= Goes down a bit level in the needed lists and recaches
+= everything from the lower level
+=
+======================
+*/
+
+void CA_DownLevel (void)
+{
+	if (!ca_levelnum)
+		Quit ("CA_DownLevel: Down past level 0!");
+	ca_levelbit>>=1;
+	ca_levelnum--;
+	CA_CacheMarks(NULL);
+}
+
+//===========================================================================
+
+/*
+======================
+=
+= CA_ClearMarks
+=
+= Clears out all the marks at the current level
+=
+======================
+*/
+
+void CA_ClearMarks (void)
+{
+	int i;
+
+	for (i=0;i<NUMCHUNKS;i++)
+		grneeded[i]&=~ca_levelbit;
+}
+
+
+//===========================================================================
+
+/*
+======================
+=
+= CA_ClearAllMarks
+=
+= Clears out all the marks on all the levels
+=
+======================
+*/
+
+void CA_ClearAllMarks (void)
+{
+	_fmemset (grneeded,0,sizeof(grneeded));
+	ca_levelbit = 1;
+	ca_levelnum = 0;
+}
+
+
+//===========================================================================
+
+/*
+======================
+=
+= CA_FreeGraphics
+=
+======================
+*/
+
+void CA_FreeGraphics (void)
+{
+	int	i;
+
+	for (i=0;i<NUMCHUNKS;i++)
+		if (grsegs[i])
+			MM_SetPurge (&(memptr)grsegs[i],3);
+}
+
+
+/*
+======================
+=
+= CA_SetAllPurge
+=
+= Make everything possible purgable
+=
+======================
+*/
+
+void CA_SetAllPurge (void)
+{
+	int i;
+
+	CA_ClearMarks ();
+
+//
+// free cursor sprite and background save
+//
+	VW_FreeCursor ();
+
+//
+// free map headers and map planes
+//
+	for (i=0;i<NUMMAPS;i++)
+		if (mapheaderseg[i])
+			MM_SetPurge (&(memptr)mapheaderseg[i],3);
+
+	for (i=0;i<3;i++)
+		if (mapsegs[i])
+			MM_FreePtr (&(memptr)mapsegs[i]);
+
+//
+// free sounds
+//
+	for (i=0;i<NUMSNDCHUNKS;i++)
+		if (audiosegs[i])
+			MM_SetPurge (&(memptr)audiosegs[i],3);
+
+//
+// free graphics
+//
+	CA_FreeGraphics ();
+}
+
+
+void CA_SetGrPurge (void)
+{
+	int i;
+
+//
+// free graphics
+//
+	for (i=0;i<NUMCHUNKS;i++)
+		if (grsegs[i])
+			MM_SetPurge (&(memptr)grsegs[i],3);
+}
+
+
+//===========================================================================
+
+
+/*
+======================
+=
+= CAL_DialogDraw
+=
+======================
+*/
+
+#define NUMBARS	(17l*8)
+#define BARSTEP	8
+
+unsigned	thx,thy,lastx;
+long		barx,barstep;
+
+void	CAL_DialogDraw (char *title,unsigned numcache)
+{
+	unsigned	homex,homey,x;
+
+	barstep = (NUMBARS<<16)/numcache;
+
+//
+// draw dialog window (masked tiles 12 - 20 are window borders)
+//
+	US_CenterWindow (20,8);
+	homex = PrintX;
+	homey = PrintY;
+
+	US_CPrint ("Loading");
+	fontcolor = F_SECONDCOLOR;
+	US_CPrint (title);
+	fontcolor = F_BLACK;
+
+//
+// draw thermometer bar
+//
+	thx = homex + 8;
+	thy = homey + 32;
+#ifdef CAT3D
+	VWB_DrawTile8(thx,thy,0);		// CAT3D numbers
+	VWB_DrawTile8(thx,thy+8,3);
+	VWB_DrawTile8(thx,thy+16,6);
+	VWB_DrawTile8(thx+17*8,thy,2);
+	VWB_DrawTile8(thx+17*8,thy+8,5);
+	VWB_DrawTile8(thx+17*8,thy+16,8);
+	for (x=thx+8;x<thx+17*8;x+=8)
+	{
+		VWB_DrawTile8(x,thy,1);
+		VWB_DrawTile8(x,thy+8,4);
+		VWB_DrawTile8(x,thy+16,7);
+	}
+#else
+	VWB_DrawTile8(thx,thy,11);		// KEEN numbers
+	VWB_DrawTile8(thx,thy+8,14);
+	VWB_DrawTile8(thx,thy+16,17);
+	VWB_DrawTile8(thx+17*8,thy,13);
+	VWB_DrawTile8(thx+17*8,thy+8,16);
+	VWB_DrawTile8(thx+17*8,thy+16,19);
+	for (x=thx+8;x<thx+17*8;x+=8)
+	{
+		VWB_DrawTile8(x,thy,12);
+		VWB_DrawTile8(x,thy+8,15);
+		VWB_DrawTile8(x,thy+16,18);
+	}
+#endif
+
+	thx += 4;		// first line location
+	thy += 5;
+	barx = (long)thx<<16;
+	lastx = thx;
+
+	VW_UpdateScreen();
+}
+
+
+/*
+======================
+=
+= CAL_DialogUpdate
+=
+======================
+*/
+
+void	CAL_DialogUpdate (void)
+{
+	unsigned	x,xh;
+
+	barx+=barstep;
+	xh = barx>>16;
+	if (xh - lastx > BARSTEP)
+	{
+		for (x=lastx;x<=xh;x++)
+#if GRMODE == EGAGR
+			VWB_Vlin (thy,thy+13,x,14);
+#endif
+#if GRMODE == CGAGR
+			VWB_Vlin (thy,thy+13,x,SECONDCOLOR);
+#endif
+		lastx = xh;
+		VW_UpdateScreen();
+	}
+}
+
+/*
+======================
+=
+= CAL_DialogFinish
+=
+======================
+*/
+
+void	CAL_DialogFinish (void)
+{
+	unsigned	x,xh;
+
+	xh = thx + NUMBARS;
+	for (x=lastx;x<=xh;x++)
+#if GRMODE == EGAGR
+		VWB_Vlin (thy,thy+13,x,14);
+#endif
+#if GRMODE == CGAGR
+		VWB_Vlin (thy,thy+13,x,SECONDCOLOR);
+#endif
+	VW_UpdateScreen();
+
+}
+
+//===========================================================================
+
+/*
+======================
+=
+= CA_CacheMarks
+=
+======================
+*/
+#define MAXEMPTYREAD	1024
+
+void CA_CacheMarks (char *title)
+{
+	boolean dialog;
+	int 	i,next,numcache;
+	long	pos,endpos,nextpos,nextendpos,compressed;
+	long	bufferstart,bufferend;	// file position of general buffer
+	byte	far *source;
+	memptr	bigbufferseg;
+
+	dialog = (title!=NULL);
+
+	numcache = 0;
+//
+// go through and make everything not needed purgable
+//
+	for (i=0;i<NUMCHUNKS;i++)
+		if (grneeded[i]&ca_levelbit)
+		{
+			if (grsegs[i])					// its allready in memory, make
+				MM_SetPurge(&grsegs[i],0);	// sure it stays there!
+			else
+				numcache++;
+		}
+		else
+		{
+			if (grsegs[i])					// not needed, so make it purgeable
+				MM_SetPurge(&grsegs[i],3);
+		}
+
+	if (!numcache)			// nothing to cache!
+		return;
+
+	if (dialog)
+	{
+#ifdef PROFILE
+		write(profilehandle,title,strlen(title));
+		write(profilehandle,"\n",1);
+#endif
+		if (drawcachebox)
+			drawcachebox(title,numcache);
+	}
+
+//
+// go through and load in anything still needed
+//
+	bufferstart = bufferend = 0;		// nothing good in buffer now
+
+	for (i=0;i<NUMCHUNKS;i++)
+		if ( (grneeded[i]&ca_levelbit) && !grsegs[i])
+		{
+//
+// update thermometer
+//
+			if (dialog && updatecachebox)
+				updatecachebox ();
+
+			pos = GRFILEPOS(i);
+			if (pos<0)
+				continue;
+
+			next = i +1;
+			while (GRFILEPOS(next) == -1)		// skip past any sparse tiles
+				next++;
+
+			compressed = GRFILEPOS(next)-pos;
+			endpos = pos+compressed;
+
+			if (compressed<=BUFFERSIZE)
+			{
+				if (bufferstart<=pos
+				&& bufferend>= endpos)
+				{
+				// data is allready in buffer
+					source = (byte _seg *)bufferseg+(pos-bufferstart);
+				}
+				else
+				{
+				// load buffer with a new block from disk
+				// try to get as many of the needed blocks in as possible
+					while ( next < NUMCHUNKS )
+					{
+						while (next < NUMCHUNKS &&
+						!(grneeded[next]&ca_levelbit && !grsegs[next]))
+							next++;
+						if (next == NUMCHUNKS)
+							continue;
+
+						nextpos = GRFILEPOS(next);
+						while (GRFILEPOS(++next) == -1)	// skip past any sparse tiles
+							;
+						nextendpos = GRFILEPOS(next);
+						if (nextpos - endpos <= MAXEMPTYREAD
+						&& nextendpos-pos <= BUFFERSIZE)
+							endpos = nextendpos;
+						else
+							next = NUMCHUNKS;			// read pos to posend
+					}
+
+					lseek(grhandle,pos,SEEK_SET);
+					CA_FarRead(grhandle,bufferseg,endpos-pos);
+					bufferstart = pos;
+					bufferend = endpos;
+					source = bufferseg;
+				}
+			}
+			else
+			{
+			// big chunk, allocate temporary buffer
+				MM_GetPtr(&bigbufferseg,compressed);
+				if (mmerror)
+					return;
+				MM_SetLock (&bigbufferseg,true);
+				lseek(grhandle,pos,SEEK_SET);
+				CA_FarRead(grhandle,bigbufferseg,compressed);
+				source = bigbufferseg;
+			}
+
+			CAL_ExpandGrChunk (i,source);
+			if (mmerror)
+				return;
+
+			if (compressed>BUFFERSIZE)
+				MM_FreePtr(&bigbufferseg);
+
+		}
+
+//
+// finish up any thermometer remnants
+//
+		if (dialog && finishcachebox)
+			finishcachebox();
+}
+
diff --git a/16/keen456/KEEN4-6/ID_CA.H b/16/keen456/KEEN4-6/ID_CA.H
new file mode 100755
index 00000000..a1737872
--- /dev/null
+++ b/16/keen456/KEEN4-6/ID_CA.H
@@ -0,0 +1,152 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+// ID_CA.H
+
+#ifndef __TYPES__
+#include "ID_TYPES.H"
+#endif
+
+#ifndef __ID_MM__
+#include "ID_MM.H"
+#endif
+
+#ifndef __ID_GLOB__
+#include "ID_GLOB.H"
+#endif
+
+#define __ID_CA__
+
+//===========================================================================
+
+//#define NOMAPS
+//#define NOGRAPHICS
+//#define NOAUDIO
+
+#define MAPHEADERLINKED
+#define GRHEADERLINKED
+#define AUDIOHEADERLINKED
+
+#define NUMMAPS		30
+#define MAPPLANES	3
+
+#ifndef CAT3D
+//
+// tile info defines, as bytes after tinf the table starts
+//
+
+
+//
+// TILEINFO offsets
+//
+#define SPEED		402
+#define ANIM		(SPEED+NUMTILE16)
+
+//
+// TILEINFOM offsets
+//
+#define NORTHWALL		(ANIM+NUMTILE16)
+#define EASTWALL		(NORTHWALL+NUMTILE16M)
+#define SOUTHWALL		(EASTWALL+NUMTILE16M)
+#define WESTWALL		(SOUTHWALL+NUMTILE16M)
+#define MANIM		(WESTWALL+NUMTILE16M)
+#define INTILE		(MANIM+NUMTILE16M)
+#define MSPEED		(INTILE+NUMTILE16M)
+#endif
+
+//===========================================================================
+
+typedef	struct
+{
+	long		planestart[3];
+	unsigned	planelength[3];
+	unsigned	width,height;
+	char		name[16];
+} maptype;
+
+//===========================================================================
+
+extern	byte 		_seg	*tinf;
+extern	int			mapon;
+
+extern	unsigned	_seg	*mapsegs[3];
+extern	maptype		_seg	*mapheaderseg[NUMMAPS];
+extern	byte		_seg	*audiosegs[NUMSNDCHUNKS];
+extern	void		_seg	*grsegs[NUMCHUNKS];
+
+extern	byte		far	grneeded[NUMCHUNKS];
+extern	byte		ca_levelbit,ca_levelnum;
+
+extern	char		*titleptr[8];
+
+extern	int			profilehandle,debughandle;
+
+//
+// hooks for custom cache dialogs
+//
+extern	void	(*drawcachebox)		(char *title, unsigned numcache);
+extern	void	(*updatecachebox)	(void);
+extern	void	(*finishcachebox)	(void);
+
+//===========================================================================
+
+// just for the score box reshifting
+
+void CAL_ShiftSprite (unsigned segment,unsigned source,unsigned dest,
+	unsigned width, unsigned height, unsigned pixshift);
+
+//===========================================================================
+
+void CA_OpenDebug (void);
+void CA_CloseDebug (void);
+boolean CA_FarRead (int handle, byte far *dest, long length);
+boolean CA_FarWrite (int handle, byte far *source, long length);
+boolean CA_ReadFile (char *filename, memptr *ptr);
+boolean CA_LoadFile (char *filename, memptr *ptr);
+
+long CA_RLEWCompress (unsigned huge *source, long length, unsigned huge *dest,
+  unsigned rlewtag);
+
+void CA_RLEWexpand (unsigned huge *source, unsigned huge *dest,long length,
+  unsigned rlewtag);
+
+void CA_Startup (void);
+void CA_Shutdown (void);
+
+void CA_CacheAudioChunk (int chunk);
+void CA_LoadAllSounds (void);
+
+void CA_UpLevel (void);
+void CA_DownLevel (void);
+
+void CA_SetAllPurge (void);
+
+void CA_ClearMarks (void);
+void CA_ClearAllMarks (void);
+
+#define CA_MarkGrChunk(chunk)	grneeded[chunk]|=ca_levelbit
+
+void CA_CacheGrChunk (int chunk);
+void CA_CacheMap (int mapnum);
+
+void CA_CacheMarks (char *title);
+
diff --git a/16/keen456/KEEN4-6/ID_IN.C b/16/keen456/KEEN4-6/ID_IN.C
new file mode 100755
index 00000000..bb6929e0
--- /dev/null
+++ b/16/keen456/KEEN4-6/ID_IN.C
@@ -0,0 +1,1243 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+//
+//	ID Engine
+//	ID_IN.c - Input Manager
+//	v1.0d1
+//	By Jason Blochowiak
+//
+
+//
+//	This module handles dealing with the various input devices
+//
+//	Depends on: Memory Mgr (for demo recording), Sound Mgr (for timing stuff),
+//				User Mgr (for command line parms)
+//
+//	Globals:
+//		LastScan - The keyboard scan code of the last key pressed
+//		LastASCII - The ASCII value of the last key pressed
+//	DEBUG - there are more globals
+//
+
+#include "ID_HEADS.H"
+#pragma	hdrstop
+
+#define	KeyInt	9	// The keyboard ISR number
+
+// Stuff for the joystick
+#define	JoyScaleMax		32768
+#define	JoyScaleShift	8
+#define	MaxJoyValue		5000
+
+// 	Global variables
+		boolean		Keyboard[NumCodes],
+					JoysPresent[MaxJoys],
+					MousePresent;
+		boolean		Paused;
+		char		LastASCII;
+		ScanCode	LastScan;
+		KeyboardDef	KbdDefs[MaxKbds] = {{0x1d,0x38,0x47,0x48,0x49,0x4b,0x4d,0x4f,0x50,0x51}};
+		JoystickDef	JoyDefs[MaxJoys];
+		ControlType	Controls[MaxPlayers];
+		boolean	GravisGamepad;
+		word		GravisAction[4];
+		word		GravisMap[4];
+
+		boolean	Latch;
+		long	MouseDownCount;
+		boolean	LatchedButton0[MaxPlayers];
+		boolean	LatchedButton1[MaxPlayers];
+
+		Demo		DemoMode = demo_Off;
+		byte _seg	*DemoBuffer;
+		word		DemoOffset,DemoSize;
+
+//	Internal variables
+static	boolean		IN_Started;
+static	boolean		CapsLock;
+static	ScanCode	CurCode,LastCode;
+static	byte        far ASCIINames[] =		// Unshifted ASCII for scan codes
+					{
+//	 0   1   2   3   4   5   6   7   8   9   A   B   C   D   E   F
+	0  ,27 ,'1','2','3','4','5','6','7','8','9','0','-','=',8  ,9  ,	// 0
+	'q','w','e','r','t','y','u','i','o','p','[',']',13 ,0  ,'a','s',	// 1
+	'd','f','g','h','j','k','l',';',39 ,'`',0  ,92 ,'z','x','c','v',	// 2
+	'b','n','m',',','.','/',0  ,'*',0  ,' ',0  ,0  ,0  ,0  ,0  ,0  ,	// 3
+	0  ,0  ,0  ,0  ,0  ,0  ,0  ,'7','8','9','-','4','5','6','+','1',	// 4
+	'2','3','0',127,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,	// 5
+	0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,	// 6
+	0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0		// 7
+					},
+					far ShiftNames[] =		// Shifted ASCII for scan codes
+					{
+//	 0   1   2   3   4   5   6   7   8   9   A   B   C   D   E   F
+	0  ,27 ,'!','@','#','$','%','^','&','*','(',')','_','+',8  ,9  ,	// 0
+	'Q','W','E','R','T','Y','U','I','O','P','{','}',13 ,0  ,'A','S',	// 1
+	'D','F','G','H','J','K','L',':',34 ,'~',0  ,'|','Z','X','C','V',	// 2
+	'B','N','M','<','>','?',0  ,'*',0  ,' ',0  ,0  ,0  ,0  ,0  ,0  ,	// 3
+	0  ,0  ,0  ,0  ,0  ,0  ,0  ,'7','8','9','-','4','5','6','+','1',	// 4
+	'2','3','0',127,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,	// 5
+	0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,	// 6
+	0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0   	// 7
+					},
+					far SpecialNames[] =	// ASCII for 0xe0 prefixed codes
+					{
+//	 0   1   2   3   4   5   6   7   8   9   A   B   C   D   E   F
+	0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,	// 0
+	0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,13 ,0  ,0  ,0  ,	// 1
+	0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,	// 2
+	0  ,0  ,0  ,0  ,0  ,'/',0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,	// 3
+	0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,	// 4
+	0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,	// 5
+	0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,	// 6
+	0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0  ,0   	// 7
+					},
+
+					*ScanNames[] =		// Scan code names with single chars
+					{
+	"?","?","1","2","3","4","5","6","7","8","9","0","-","+","?","?",
+	"Q","W","E","R","T","Y","U","I","O","P","[","]","|","?","A","S",
+	"D","F","G","H","J","K","L",";","\"","?","?","?","Z","X","C","V",
+	"B","N","M",",",".","/","?","?","?","?","?","?","?","?","?","?",
+	"?","?","?","?","?","?","?","?","\xf","?","-","\x15","5","\x11","+","?",
+	"\x13","?","?","?","?","?","?","?","?","?","?","?","?","?","?","?",
+	"?","?","?","?","?","?","?","?","?","?","?","?","?","?","?","?",
+	"?","?","?","?","?","?","?","?","?","?","?","?","?","?","?","?"
+					},	// DEBUG - consolidate these
+					far ExtScanCodes[] =	// Scan codes with >1 char names
+					{
+	1,0xe,0xf,0x1d,0x2a,0x39,0x3a,0x3b,0x3c,0x3d,0x3e,
+	0x3f,0x40,0x41,0x42,0x43,0x44,0x57,0x59,0x46,0x1c,0x36,
+	0x37,0x38,0x47,0x49,0x4f,0x51,0x52,0x53,0x45,0x48,
+	0x50,0x4b,0x4d,0x00
+					},
+					*ExtScanNames[] =	// Names corresponding to ExtScanCodes
+					{
+	"Esc","BkSp","Tab","Ctrl","LShft","Space","CapsLk","F1","F2","F3","F4",
+	"F5","F6","F7","F8","F9","F10","F11","F12","ScrlLk","Enter","RShft",
+	"PrtSc","Alt","Home","PgUp","End","PgDn","Ins","Del","NumLk","Up",
+	"Down","Left","Right",""
+					};
+static	Direction	DirTable[] =		// Quick lookup for total direction
+					{
+						dir_NorthWest,	dir_North,	dir_NorthEast,
+						dir_West,		dir_None,	dir_East,
+						dir_SouthWest,	dir_South,	dir_SouthEast
+					};
+
+static	void			(*INL_KeyHook)(void);
+static	void interrupt	(*OldKeyVect)(void);
+
+static	char			*ParmStrings[] = {"nojoys","nomouse",nil};
+
+//	Internal routines
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	INL_KeyService() - Handles a keyboard interrupt (key up/down)
+//
+///////////////////////////////////////////////////////////////////////////
+static void interrupt
+INL_KeyService(void)
+{
+static	boolean	special;
+		byte	k,c,
+				temp;
+		int	player;
+
+	k = inportb(0x60);	// Get the scan code
+
+	// Tell the XT keyboard controller to clear the key
+	outportb(0x61,(temp = inportb(0x61)) | 0x80);
+	outportb(0x61,temp);
+
+	if (k == 0xe0)		// Special key prefix
+		special = true;
+	else if (k == 0xe1)	// Handle Pause key
+		Paused = true;
+	else
+	{
+		if (k & 0x80)	// Break code
+		{
+			k &= 0x7f;
+
+// DEBUG - handle special keys: ctl-alt-delete, print scrn
+
+			Keyboard[k] = false;
+		}
+		else			// Make code
+		{
+			LastCode = CurCode;
+			CurCode = LastScan = k;
+			Keyboard[k] = true;
+
+			if (Latch)
+			{
+				for (player = 0; player < MaxPlayers; player++)
+				{
+					if (Controls[player] == ctrl_Keyboard1)
+					{
+						if (CurCode == KbdDefs[0].button0)
+							LatchedButton0[player] = true;
+						else if (CurCode == KbdDefs[0].button1)
+							LatchedButton1[player] = true;
+					}
+					else if (Controls[player] == ctrl_Keyboard1)	// BUG? should probably check for ctrl_Keyboard2 here...
+					{
+						if (CurCode == KbdDefs[1].button0)
+							LatchedButton0[player] = true;
+						else if (CurCode == KbdDefs[1].button1)
+							LatchedButton1[player] = true;
+					}
+				}
+			}
+
+			if (special)
+				c = SpecialNames[k];
+			else
+			{
+				if (k == sc_CapsLock)
+				{
+					CapsLock ^= true;
+					// DEBUG - make caps lock light work
+				}
+
+				if (Keyboard[sc_LShift] || Keyboard[sc_RShift])	// If shifted
+				{
+					c = ShiftNames[k];
+					if ((c >= 'A') && (c <= 'Z') && CapsLock)
+						c += 'a' - 'A';
+				}
+				else
+				{
+					c = ASCIINames[k];
+					if ((c >= 'a') && (c <= 'z') && CapsLock)
+						c -= 'a' - 'A';
+				}
+			}
+			if (c)
+				LastASCII = c;
+		}
+
+		special = false;
+	}
+
+	if (INL_KeyHook && !special)
+		INL_KeyHook();
+	outportb(0x20,0x20);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	INL_GetMouseDelta() - Gets the amount that the mouse has moved from the
+//		mouse driver
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+INL_GetMouseDelta(int *x,int *y)
+{
+	Mouse(MDelta);
+	*x = _CX;
+	*y = _DX;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	INL_GetMouseButtons() - Gets the status of the mouse buttons from the
+//		mouse driver
+//
+///////////////////////////////////////////////////////////////////////////
+static word
+INL_GetMouseButtons(void)
+{
+	word	buttons;
+
+	Mouse(MButtons);
+	buttons = _BX;
+	return(buttons);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_GetJoyAbs() - Reads the absolute position of the specified joystick
+//
+///////////////////////////////////////////////////////////////////////////
+void
+IN_GetJoyAbs(word joy,word *xp,word *yp)
+{
+	byte	xb,yb,
+			xs,ys;
+	word	x,y;
+
+	x = y = 0;
+	xs = joy? 2 : 0;		// Find shift value for x axis
+	xb = 1 << xs;			// Use shift value to get x bit mask
+	ys = joy? 3 : 1;		// Do the same for y axis
+	yb = 1 << ys;
+
+// Read the absolute joystick values
+asm		pushf				// Save some registers
+asm		push	si
+asm		push	di
+asm		cli					// Make sure an interrupt doesn't screw the timings
+
+
+asm		mov		dx,0x201
+asm		in		al,dx
+asm		out		dx,al		// Clear the resistors
+
+asm		mov		ah,[xb]		// Get masks into registers
+asm		mov		ch,[yb]
+
+asm		xor		si,si		// Clear count registers
+asm		xor		di,di
+asm		xor		bh,bh		// Clear high byte of bx for later
+
+asm		push	bp			// Don't mess up stack frame
+asm		mov		bp,MaxJoyValue
+
+loop:
+asm		in		al,dx		// Get bits indicating whether all are finished
+
+asm		dec		bp			// Check bounding register
+asm		jz		done		// We have a silly value - abort
+
+asm		mov		bl,al		// Duplicate the bits
+asm		and		bl,ah		// Mask off useless bits (in [xb])
+asm		add		si,bx		// Possibly increment count register
+asm		mov		cl,bl		// Save for testing later
+
+asm		mov		bl,al
+asm		and		bl,ch		// [yb]
+asm		add		di,bx
+
+asm		add		cl,bl
+asm		jnz		loop 		// If both bits were 0, drop out
+
+done:
+asm     pop		bp
+
+asm		mov		cl,[xs]		// Get the number of bits to shift
+asm		shr		si,cl		//  and shift the count that many times
+
+asm		mov		cl,[ys]
+asm		shr		di,cl
+
+asm		mov		[x],si		// Store the values into the variables
+asm		mov		[y],di
+
+asm		pop		di
+asm		pop		si
+asm		popf				// Restore the registers
+
+	*xp = x;
+	*yp = y;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	INL_GetJoyDelta() - Returns the relative movement of the specified
+//		joystick (from +/-127, scaled adaptively)
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+INL_GetJoyDelta(word joy,int *dx,int *dy,boolean adaptive)
+{
+	word		x,y;
+	longword	time;
+	JoystickDef	*def;
+static	longword	lasttime;
+
+	IN_GetJoyAbs(joy,&x,&y);
+	def = JoyDefs + joy;
+
+	if (x < def->threshMinX)
+	{
+		if (x < def->joyMinX)
+			x = def->joyMinX;
+
+		x = -(x - def->threshMinX);
+		x *= def->joyMultXL;
+		x >>= JoyScaleShift;
+		*dx = (x > 127)? -127 : -x;
+	}
+	else if (x > def->threshMaxX)
+	{
+		if (x > def->joyMaxX)
+			x = def->joyMaxX;
+
+		x = x - def->threshMaxX;
+		x *= def->joyMultXH;
+		x >>= JoyScaleShift;
+		*dx = (x > 127)? 127 : x;
+	}
+	else
+		*dx = 0;
+
+	if (y < def->threshMinY)
+	{
+		if (y < def->joyMinY)
+			y = def->joyMinY;
+
+		y = -(y - def->threshMinY);
+		y *= def->joyMultYL;
+		y >>= JoyScaleShift;
+		*dy = (y > 127)? -127 : -y;
+	}
+	else if (y > def->threshMaxY)
+	{
+		if (y > def->joyMaxY)
+			y = def->joyMaxY;
+
+		y = y - def->threshMaxY;
+		y *= def->joyMultYH;
+		y >>= JoyScaleShift;
+		*dy = (y > 127)? 127 : y;
+	}
+	else
+		*dy = 0;
+
+	if (adaptive)
+	{
+		time = (TimeCount - lasttime) / 2;
+		if (time)
+		{
+			if (time > 8)
+				time = 8;
+			*dx *= time;
+			*dy *= time;
+		}
+	}
+	lasttime = TimeCount;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	INL_GetJoyButtons() - Returns the button status of the specified
+//		joystick
+//
+///////////////////////////////////////////////////////////////////////////
+static word
+INL_GetJoyButtons(word joy)
+{
+register	word	result;
+
+	result = inportb(0x201);	// Get all the joystick buttons
+	if (joy == 2)
+	{
+		// all 4 buttons (for Gravis Gamepad option)
+		result >>= 4;
+		result &= 15;
+		result ^= 15;
+	}
+	else
+	{
+		result >>= joy? 6 : 4;	// Shift into bits 0-1
+		result &= 3;				// Mask off the useless bits
+		result ^= 3;
+	}
+	return(result);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_GetJoyButtonsDB() - Returns the de-bounced button status of the
+//		specified joystick
+//
+///////////////////////////////////////////////////////////////////////////
+word
+IN_GetJoyButtonsDB(word joy)
+{
+	longword	endtime;
+	word		result1,result2;
+
+	do
+	{
+		result1 = INL_GetJoyButtons(joy);
+		endtime = TimeCount + 2;
+		while (TimeCount <= endtime)
+			;
+		result2 = INL_GetJoyButtons(joy);
+	} while (result1 != result2);
+	return(result1);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	INL_StartKbd() - Sets up my keyboard stuff for use
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+INL_StartKbd(void)
+{
+	INL_KeyHook = 0;	// Clear key hook
+
+	IN_ClearKeysDown();
+
+	OldKeyVect = getvect(KeyInt);
+	setvect(KeyInt,INL_KeyService);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	INL_ShutKbd() - Restores keyboard control to the BIOS
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+INL_ShutKbd(void)
+{
+	poke(0x40,0x17,peek(0x40,0x17) & 0xfaf0);	// Clear ctrl/alt/shift flags
+
+	setvect(KeyInt,OldKeyVect);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	INL_StartMouse() - Detects and sets up the mouse
+//
+///////////////////////////////////////////////////////////////////////////
+static boolean
+INL_StartMouse(void)
+{
+	if (getvect(MouseInt))
+	{
+		Mouse(MReset);
+		if (_AX == 0xffff)
+			return(true);
+	}
+	return(false);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	INL_ShutMouse() - Cleans up after the mouse
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+INL_ShutMouse(void)
+{
+}
+
+//
+//	INL_SetJoyScale() - Sets up scaling values for the specified joystick
+//
+static void
+INL_SetJoyScale(word joy)
+{
+	JoystickDef	*def;
+
+	def = &JoyDefs[joy];
+	def->joyMultXL = JoyScaleMax / (def->threshMinX - def->joyMinX);
+	def->joyMultXH = JoyScaleMax / (def->joyMaxX - def->threshMaxX);
+	def->joyMultYL = JoyScaleMax / (def->threshMinY - def->joyMinY);
+	def->joyMultYH = JoyScaleMax / (def->joyMaxY - def->threshMaxY);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_SetupJoy() - Sets up thresholding values and calls INL_SetJoyScale()
+//		to set up scaling values
+//
+///////////////////////////////////////////////////////////////////////////
+void
+IN_SetupJoy(word joy,word minx,word maxx,word miny,word maxy)
+{
+	word		d,r;
+	JoystickDef	*def;
+
+	def = &JoyDefs[joy];
+
+	def->joyMinX = minx;
+	def->joyMaxX = maxx;
+	r = maxx - minx;
+	d = r / 5;
+	def->threshMinX = ((r / 2) - d) + minx;
+	def->threshMaxX = ((r / 2) + d) + minx;
+
+	def->joyMinY = miny;
+	def->joyMaxY = maxy;
+	r = maxy - miny;
+	d = r / 5;
+	def->threshMinY = ((r / 2) - d) + miny;
+	def->threshMaxY = ((r / 2) + d) + miny;
+
+	INL_SetJoyScale(joy);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	INL_StartJoy() - Detects & auto-configures the specified joystick
+//					The auto-config assumes the joystick is centered
+//
+///////////////////////////////////////////////////////////////////////////
+static boolean
+INL_StartJoy(word joy)
+{
+	word		x,y;
+
+	IN_GetJoyAbs(joy,&x,&y);
+
+	if
+	(
+		((x == 0) || (x > MaxJoyValue - 10))
+	||	((y == 0) || (y > MaxJoyValue - 10))
+	)
+		return(false);
+	else
+	{
+		IN_SetupJoy(joy,0,x * 2,0,y * 2);
+		return(true);
+	}
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	INL_ShutJoy() - Cleans up the joystick stuff
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+INL_ShutJoy(word joy)
+{
+	JoysPresent[joy] = false;
+}
+
+//	Public routines
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_ClearButtonLatch() - Clears the button latch stuff
+//
+///////////////////////////////////////////////////////////////////////////
+void
+IN_ClearButtonLatch(void)
+{
+	int player;
+
+asm		pushf
+asm		cli
+
+	MouseDownCount = 0;
+
+	for (player = 0; player < MaxPlayers; player++)
+	{
+		LatchedButton0[player] = LatchedButton1[player] = 0;
+	}
+
+asm		popf
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	LatchSndHook() - Hook routine for joystick button latch
+//
+///////////////////////////////////////////////////////////////////////////
+void
+LatchSndHook(void)
+{
+	int player;
+	ControlType ctrl;
+	word buttons;
+
+	for (player = 0; player < MaxPlayers; player++)
+	{
+		ctrl = Controls[player];
+
+		if (ctrl == ctrl_Joystick1 || ctrl == ctrl_Joystick2)
+		{
+			buttons = INL_GetJoyButtons(ctrl - ctrl_Joystick1);
+
+			if (buttons & 1)
+				LatchedButton0[player] = true;
+			if (buttons & 2)
+				LatchedButton1[player] = true;
+		}
+	}
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_LatchButtons() - Enables or disables button latch
+//
+///////////////////////////////////////////////////////////////////////////
+void IN_LatchButtons(boolean enabled)
+{
+	if (enabled)
+	{
+		Latch = false;
+		IN_ClearButtonLatch();
+	}
+
+	Latch = enabled;
+	SD_SetUserHook(Latch ? LatchSndHook : NULL);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_Startup() - Starts up the Input Mgr
+//
+///////////////////////////////////////////////////////////////////////////
+void
+IN_Startup(void)
+{
+	boolean	checkjoys,checkmouse;
+	word	i;
+
+	if (IN_Started)
+		return;
+
+	checkjoys = true;
+	checkmouse = true;
+	for (i = 1;i < _argc;i++)
+	{
+		switch (US_CheckParm(_argv[i],ParmStrings))
+		{
+		case 0:
+			checkjoys = false;
+			break;
+		case 1:
+			checkmouse = false;
+			break;
+		}
+	}
+
+	INL_StartKbd();
+	MousePresent = checkmouse? INL_StartMouse() : false;
+
+	for (i = 0;i < MaxJoys;i++)
+		JoysPresent[i] = checkjoys? INL_StartJoy(i) : false;
+
+	IN_Started = true;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_Default() - Sets up default conditions for the Input Mgr
+//
+///////////////////////////////////////////////////////////////////////////
+void
+IN_Default(boolean gotit,ControlType in)
+{
+	if
+	(
+		(!gotit)
+	|| 	((in == ctrl_Joystick1) && !JoysPresent[0])
+	|| 	((in == ctrl_Joystick2) && !JoysPresent[1])
+	|| 	((in == ctrl_Mouse) && !MousePresent)
+	)
+		in = ctrl_Keyboard1;
+	IN_SetControlType(0,in);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_Shutdown() - Shuts down the Input Mgr
+//
+///////////////////////////////////////////////////////////////////////////
+void
+IN_Shutdown(void)
+{
+	word	i;
+
+	if (!IN_Started)
+		return;
+
+	INL_ShutMouse();
+	for (i = 0;i < MaxJoys;i++)
+		INL_ShutJoy(i);
+	INL_ShutKbd();
+
+	IN_Started = false;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_SetKeyHook() - Sets the routine that gets called by INL_KeyService()
+//			everytime a real make/break code gets hit
+//
+///////////////////////////////////////////////////////////////////////////
+void
+IN_SetKeyHook(void (*hook)())
+{
+	// BUG: interrupts should be disabled while setting INL_KeyHook!
+	INL_KeyHook = hook;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_ClearKeyDown() - Clears the keyboard array
+//
+///////////////////////////////////////////////////////////////////////////
+void
+IN_ClearKeysDown(void)
+{
+	int	i;
+
+	LastScan = sc_None;
+	LastASCII = key_None;
+	for (i = 0;i < NumCodes;i++)
+		Keyboard[i] = false;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	INL_AdjustCursor() - Internal routine of common code from IN_ReadCursor()
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+INL_AdjustCursor(CursorInfo *info,word buttons,int dx,int dy)
+{
+	if (buttons & (1 << 0))
+		info->button0 = true;
+	if (buttons & (1 << 1))
+		info->button1 = true;
+
+	info->x += dx;
+	info->y += dy;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_ReadCursor() - Reads the input devices and fills in the cursor info
+//		struct
+//
+///////////////////////////////////////////////////////////////////////////
+void
+IN_ReadCursor(CursorInfo *info)
+{
+	word	i,
+		player,
+			buttons;
+	int		dx,dy;
+
+	info->x = info->y = 0;
+	info->button0 = info->button1 = false;
+
+	if (MousePresent)
+	{
+		buttons = INL_GetMouseButtons();
+		INL_GetMouseDelta(&dx,&dy);
+		INL_AdjustCursor(info,buttons,dx,dy);
+	}
+
+	for (i = 0;i < MaxJoys;i++)
+	{
+		if (!JoysPresent[i])
+			continue;
+
+		for (player = 0;player < MaxPlayers; player++)
+		{
+			if (Controls[player] == ctrl_Joystick1+i)
+				goto joyok;
+		}
+		continue;
+
+joyok:
+		buttons = INL_GetJoyButtons(i);
+		INL_GetJoyDelta(i,&dx,&dy,true);
+		dx /= 64;
+		dy /= 64;
+		INL_AdjustCursor(info,buttons,dx,dy);
+	}
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_ReadControl() - Reads the device associated with the specified
+//		player and fills in the control info struct
+//
+///////////////////////////////////////////////////////////////////////////
+void
+IN_ReadControl(int player,ControlInfo *info)
+{
+			boolean		realdelta;
+			byte		dbyte;
+			word		buttons;
+			int			i;
+			int			dx,dy;
+			Motion		mx,my;
+			ControlType	type;
+register	KeyboardDef	*def;
+
+	dx = dy = 0;
+	mx = my = motion_None;
+	buttons = 0;
+
+	if (DemoMode == demo_Playback)
+	{
+		dbyte = DemoBuffer[DemoOffset + 1];
+		my = (dbyte & 3) - 1;
+		mx = ((dbyte >> 2) & 3) - 1;
+		buttons = (dbyte >> 4) & 3;
+
+		if (!(--DemoBuffer[DemoOffset]))
+		{
+			DemoOffset += 2;
+			if (DemoOffset >= DemoSize)
+				DemoMode = demo_PlayDone;
+		}
+
+		realdelta = false;
+	}
+	else if (DemoMode == demo_PlayDone)
+		Quit("Demo playback exceeded");
+	else
+	{
+		switch (type = Controls[player])
+		{
+		case ctrl_Keyboard1:
+		case ctrl_Keyboard2:
+			def = &KbdDefs[type - ctrl_Keyboard];
+
+			if (Keyboard[def->upleft])
+				mx = motion_Left,my = motion_Up;
+			else if (Keyboard[def->upright])
+				mx = motion_Right,my = motion_Up;
+			else if (Keyboard[def->downleft])
+				mx = motion_Left,my = motion_Down;
+			else if (Keyboard[def->downright])
+				mx = motion_Right,my = motion_Down;
+
+			if (Keyboard[def->up])
+				my = motion_Up;
+			else if (Keyboard[def->down])
+				my = motion_Down;
+
+			if (Keyboard[def->left])
+				mx = motion_Left;
+			else if (Keyboard[def->right])
+				mx = motion_Right;
+
+			if (Keyboard[def->button0])
+				buttons += 1 << 0;
+			if (Keyboard[def->button1])
+				buttons += 1 << 1;
+			realdelta = false;
+			break;
+		case ctrl_Joystick1:
+		case ctrl_Joystick2:
+			INL_GetJoyDelta(type - ctrl_Joystick,&dx,&dy,false);
+			if (GravisGamepad)
+			{
+				buttons = INL_GetJoyButtons(2);
+				for (i=0; i<4; i++)
+				{
+					GravisAction[i] = buttons & (1 << GravisMap[i]);
+				}
+			}
+			buttons = INL_GetJoyButtons(type - ctrl_Joystick);
+			realdelta = true;
+			break;
+		case ctrl_Mouse:
+			INL_GetMouseDelta(&dx,&dy);
+			buttons = INL_GetMouseButtons();
+			realdelta = true;
+			break;
+		}
+	}
+
+	if (realdelta)
+	{
+		mx = (dx < 0)? motion_Left : ((dx > 0)? motion_Right : motion_None);
+		my = (dy < 0)? motion_Up : ((dy > 0)? motion_Down : motion_None);
+	}
+	else
+	{
+		dx = mx * 127;
+		dy = my * 127;
+	}
+
+	info->x = dx;
+	info->xaxis = mx;
+	info->y = dy;
+	info->yaxis = my;
+	info->button0 = buttons & (1 << 0);
+	info->button1 = buttons & (1 << 1);
+	info->dir = DirTable[((my + 1) * 3) + (mx + 1)];
+
+	if (DemoMode == demo_Record)
+	{
+		// Pack the control info into a byte
+		dbyte = (buttons << 4) | ((mx + 1) << 2) | (my + 1);
+
+		if
+		(
+			(DemoBuffer[DemoOffset + 1] == dbyte)
+		&&	(DemoBuffer[DemoOffset] < 255)
+		)
+			(DemoBuffer[DemoOffset])++;
+		else
+		{
+			if (DemoOffset || DemoBuffer[DemoOffset])
+				DemoOffset += 2;
+
+			if (DemoOffset >= DemoSize)
+				Quit("Demo buffer overflow");
+
+			DemoBuffer[DemoOffset] = 1;
+			DemoBuffer[DemoOffset + 1] = dbyte;
+		}
+	}
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_SetControlType() - Sets the control type to be used by the specified
+//		player
+//
+///////////////////////////////////////////////////////////////////////////
+void
+IN_SetControlType(int player,ControlType type)
+{
+	// DEBUG - check that requested type is present?
+	Controls[player] = type;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_StartDemoRecord() - Starts the demo recording, using a buffer the
+//		size passed. Returns if the buffer allocation was successful
+//
+///////////////////////////////////////////////////////////////////////////
+boolean
+IN_StartDemoRecord(word bufsize)
+{
+	if (!bufsize)
+		return(false);
+
+	MM_GetPtr((memptr *)&DemoBuffer,bufsize);
+	DemoMode = demo_Record;
+	DemoSize = bufsize & ~1;
+	DemoOffset = 0;
+	DemoBuffer[0] = DemoBuffer[1] = 0;
+
+	return(true);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_StartDemoPlayback() - Plays back the demo pointed to of the given size
+//
+///////////////////////////////////////////////////////////////////////////
+void
+IN_StartDemoPlayback(byte _seg *buffer,word bufsize)
+{
+	DemoBuffer = buffer;
+	DemoMode = demo_Playback;
+	DemoSize = bufsize & ~1;
+	DemoOffset = 0;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_StopDemo() - Turns off demo mode
+//
+///////////////////////////////////////////////////////////////////////////
+void
+IN_StopDemo(void)
+{
+	if ((DemoMode == demo_Record) && DemoOffset)
+		DemoOffset += 2;
+
+	DemoMode = demo_Off;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_FreeDemoBuffer() - Frees the demo buffer, if it's been allocated
+//
+///////////////////////////////////////////////////////////////////////////
+void
+IN_FreeDemoBuffer(void)
+{
+	if (DemoBuffer)
+		MM_FreePtr((memptr *)&DemoBuffer);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_GetScanName() - Returns a string containing the name of the
+//		specified scan code
+//
+///////////////////////////////////////////////////////////////////////////
+byte *
+IN_GetScanName(ScanCode scan)
+{
+	byte		**p;
+	ScanCode	far *s;
+
+	for (s = ExtScanCodes,p = ExtScanNames;*s;p++,s++)
+		if (*s == scan)
+			return(*p);
+
+	return(ScanNames[scan]);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_WaitForKey() - Waits for a scan code, then clears LastScan and
+//		returns the scan code
+//
+///////////////////////////////////////////////////////////////////////////
+ScanCode
+IN_WaitForKey(void)
+{
+	ScanCode	result;
+
+	while (!(result = LastScan))
+		;
+	LastScan = 0;
+	return(result);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_WaitForASCII() - Waits for an ASCII char, then clears LastASCII and
+//		returns the ASCII value
+//
+///////////////////////////////////////////////////////////////////////////
+char
+IN_WaitForASCII(void)
+{
+	char		result;
+
+	while (!(result = LastASCII))
+		;
+	LastASCII = '\0';
+	return(result);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_AckBack() - Waits for either an ASCII keypress or a button press
+//
+///////////////////////////////////////////////////////////////////////////
+void
+IN_AckBack(void)
+{
+	word	i;
+
+	while (!LastScan)
+	{
+		if (MousePresent)
+		{
+			if (INL_GetMouseButtons())
+			{
+				while (INL_GetMouseButtons())
+					;
+				return;
+			}
+		}
+
+		for (i = 0;i < MaxJoys;i++)
+		{
+			if (JoysPresent[i] || GravisGamepad)
+			{
+				if (IN_GetJoyButtonsDB(i))
+				{
+					while (IN_GetJoyButtonsDB(i))
+						;
+					return;
+				}
+			}
+		}
+	}
+
+	IN_ClearKey(LastScan);
+	LastScan = sc_None;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_Ack() - Clears user input & then calls IN_AckBack()
+//
+///////////////////////////////////////////////////////////////////////////
+void
+IN_Ack(void)
+{
+	word	i;
+
+	IN_ClearKey(LastScan);
+	LastScan = sc_None;
+
+	if (MousePresent)
+		while (INL_GetMouseButtons())
+					;
+	for (i = 0;i < MaxJoys;i++)
+		if (JoysPresent[i] || GravisGamepad)
+			while (IN_GetJoyButtonsDB(i))
+				;
+
+	IN_AckBack();
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_IsUserInput() - Returns true if a key has been pressed or a button
+//		is down
+//
+///////////////////////////////////////////////////////////////////////////
+boolean
+IN_IsUserInput(void)
+{
+	boolean	result;
+	word	i;
+
+	result = LastScan;
+
+	if (MousePresent)
+		if (INL_GetMouseButtons())
+			result = true;
+
+	for (i = 0;i < MaxJoys;i++)
+		if (JoysPresent[i] || GravisGamepad)
+			if (INL_GetJoyButtons(i))
+				result = true;
+
+	return(result);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	IN_UserInput() - Waits for the specified delay time (in ticks) or the
+//		user pressing a key or a mouse button. If the clear flag is set, it
+//		then either clears the key or waits for the user to let the mouse
+//		button up.
+//
+///////////////////////////////////////////////////////////////////////////
+boolean
+IN_UserInput(longword delay,boolean clear)
+{
+	longword	lasttime;
+
+	lasttime = TimeCount;
+	do
+	{
+		if (IN_IsUserInput())
+		{
+			if (clear)
+				IN_AckBack();
+			return(true);
+		}
+	} while (TimeCount - lasttime < delay);
+	return(false);
+}
diff --git a/16/keen456/KEEN4-6/ID_IN.H b/16/keen456/KEEN4-6/ID_IN.H
new file mode 100755
index 00000000..d3ade29f
--- /dev/null
+++ b/16/keen456/KEEN4-6/ID_IN.H
@@ -0,0 +1,232 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+//
+//	ID Engine
+//	ID_IN.h - Header file for Input Manager
+//	v1.0d1
+//	By Jason Blochowiak
+//
+
+#ifndef	__TYPES__
+#include "ID_Types.h"
+#endif
+
+#ifndef	__ID_IN__
+#define	__ID_IN__
+
+#ifdef	__DEBUG__
+#define	__DEBUG_InputMgr__
+#endif
+
+#define	MaxPlayers	4
+#define	MaxKbds		2
+#define	MaxJoys		2
+#define	NumCodes	128
+
+typedef	byte		ScanCode;
+#define	sc_None			0
+#define	sc_Bad			0xff
+#define	sc_Return		0x1c
+#define	sc_Enter		sc_Return
+#define	sc_Escape		0x01
+#define	sc_Space		0x39
+#define	sc_BackSpace	0x0e
+#define	sc_Tab			0x0f
+#define	sc_Alt			0x38
+#define	sc_Control		0x1d
+#define	sc_CapsLock		0x3a
+#define	sc_LShift		0x2a
+#define	sc_RShift		0x36
+#define	sc_UpArrow		0x48
+#define	sc_DownArrow	0x50
+#define	sc_LeftArrow	0x4b
+#define	sc_RightArrow	0x4d
+#define	sc_Insert		0x52
+#define	sc_Delete		0x53
+#define	sc_Home			0x47
+#define	sc_End			0x4f
+#define	sc_PgUp			0x49
+#define	sc_PgDn			0x51
+#define	sc_F1			0x3b
+#define	sc_F2			0x3c
+#define	sc_F3			0x3d
+#define	sc_F4			0x3e
+#define	sc_F5			0x3f
+#define	sc_F6			0x40
+#define	sc_F7			0x41
+#define	sc_F8			0x42
+#define	sc_F9			0x43
+#define	sc_F10			0x44
+#define	sc_F11			0x57
+#define	sc_F12			0x59	// BUG: F12 uses scan code 0x58!
+
+#define	sc_A			0x1e
+#define	sc_B			0x30
+#define	sc_C			0x2e
+#define	sc_D			0x20
+#define	sc_E			0x12
+#define	sc_F			0x21
+#define	sc_G			0x22
+#define	sc_H			0x23
+#define	sc_I			0x17
+#define	sc_J			0x24
+#define	sc_K			0x25
+#define	sc_L			0x26
+#define	sc_M			0x32
+#define	sc_N			0x31
+#define	sc_O			0x18
+#define	sc_P			0x19
+#define	sc_Q			0x10
+#define	sc_R			0x13
+#define	sc_S			0x1f
+#define	sc_T			0x14
+#define	sc_U			0x16
+#define	sc_V			0x2f
+#define	sc_W			0x11
+#define	sc_X			0x2d
+#define	sc_Y			0x15
+#define	sc_Z			0x2c
+
+#define	sc_1			0x02
+#define	sc_2			0x03
+#define	sc_3			0x04
+#define	sc_4			0x05
+#define	sc_5			0x06
+#define	sc_6			0x07
+#define	sc_7			0x08
+#define	sc_8			0x09
+#define	sc_9			0x0a
+#define	sc_0			0x0b
+
+#define	key_None		0
+#define	key_Return		0x0d
+#define	key_Enter		key_Return
+#define	key_Escape		0x1b
+#define	key_Space		0x20
+#define	key_BackSpace	0x08
+#define	key_Tab			0x09
+#define	key_Delete		0x7f
+
+// 	Stuff for the mouse
+#define	MReset		0
+#define	MButtons	3
+#define	MDelta		11
+
+#define	MouseInt	0x33
+#define	Mouse(x)	_AX = x,geninterrupt(MouseInt)
+
+typedef	enum		{
+						demo_Off,demo_Record,demo_Playback,demo_PlayDone
+					} Demo;
+typedef	enum		{
+						ctrl_Keyboard,
+							ctrl_Keyboard1 = ctrl_Keyboard,ctrl_Keyboard2,
+						ctrl_Joystick,
+							ctrl_Joystick1 = ctrl_Joystick,ctrl_Joystick2,
+						ctrl_Mouse
+					} ControlType;
+typedef	enum		{
+						motion_Left = -1,motion_Up = -1,
+						motion_None = 0,
+						motion_Right = 1,motion_Down = 1
+					} Motion;
+typedef	enum		{
+						dir_North,dir_NorthEast,
+						dir_East,dir_SouthEast,
+						dir_South,dir_SouthWest,
+						dir_West,dir_NorthWest,
+						dir_None
+					} Direction;
+typedef	enum		{
+						ga_Jump,
+						ga_Pogo,
+						ga_Fire,
+						ga_Status
+					} GravisAType;
+typedef	struct		{
+						boolean		button0,button1;
+						int			x,y;
+						Motion		xaxis,yaxis;
+						Direction	dir;
+					} CursorInfo;
+typedef	CursorInfo	ControlInfo;
+typedef	struct		{
+						ScanCode	button0,button1,
+									upleft,		up,		upright,
+									left,				right,
+									downleft,	down,	downright;
+					} KeyboardDef;
+typedef	struct		{
+						word		joyMinX,joyMinY,
+									threshMinX,threshMinY,
+									threshMaxX,threshMaxY,
+									joyMaxX,joyMaxY,
+									joyMultXL,joyMultYL,
+									joyMultXH,joyMultYH;
+					} JoystickDef;
+// Global variables
+extern	boolean		Keyboard[],
+					MousePresent,
+					JoysPresent[];
+extern	boolean		Paused;
+extern	char		LastASCII;
+extern	ScanCode	LastScan;
+extern	KeyboardDef	KbdDefs[];
+extern	JoystickDef	JoyDefs[];
+extern	ControlType	Controls[MaxPlayers];
+extern	boolean		GravisGamepad;
+extern	word		GravisAction[4];
+extern	word		GravisMap[4];
+
+extern	Demo		DemoMode;
+extern	byte _seg	*DemoBuffer;
+extern	word		DemoOffset,DemoSize;
+
+// Function prototypes
+#define	IN_KeyDown(code)	(Keyboard[(code)])
+#define	IN_ClearKey(code)	{Keyboard[code] = false;\
+							if (code == LastScan) LastScan = sc_None;}
+
+// DEBUG - put names in prototypes
+extern	void		IN_Startup(void),IN_Shutdown(void),
+					IN_Default(boolean gotit,ControlType in),
+					IN_SetKeyHook(void (*)()),
+					IN_ClearKeysDown(void),
+					IN_ReadCursor(CursorInfo *),
+					IN_ReadControl(int,ControlInfo *),
+					IN_SetControlType(int,ControlType),
+					IN_GetJoyAbs(word joy,word *xp,word *yp),
+					IN_SetupJoy(word joy,word minx,word maxx,
+								word miny,word maxy),
+					IN_StartDemoPlayback(byte _seg *buffer,word bufsize),
+					IN_StopDemo(void),IN_FreeDemoBuffer(void),
+					IN_Ack(void),IN_AckBack(void);
+extern	boolean		IN_UserInput(longword delay,boolean clear),
+					IN_IsUserInput(void),
+					IN_StartDemoRecord(word bufsize);
+extern	byte		*IN_GetScanName(ScanCode);
+extern	char		IN_WaitForASCII(void);
+extern	ScanCode	IN_WaitForKey(void);
+extern	word		IN_GetJoyButtonsDB(word joy);
+
+#endif
diff --git a/16/keen456/KEEN4-6/ID_MM.C b/16/keen456/KEEN4-6/ID_MM.C
new file mode 100755
index 00000000..07fdb7c2
--- /dev/null
+++ b/16/keen456/KEEN4-6/ID_MM.C
@@ -0,0 +1,1136 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+// NEWMM.C
+
+/*
+=============================================================================
+
+		   ID software memory manager
+		   --------------------------
+
+Primary coder: John Carmack
+
+RELIES ON
+---------
+Quit (char *error) function
+
+
+WORK TO DO
+----------
+MM_SizePtr to change the size of a given pointer
+
+Multiple purge levels utilized
+
+EMS / XMS unmanaged routines
+
+=============================================================================
+*/
+
+#include "ID_HEADS.H"
+#pragma hdrstop
+
+#pragma warn -pro
+#pragma warn -use
+
+/*
+=============================================================================
+
+							LOCAL INFO
+
+=============================================================================
+*/
+
+#define LOCKBIT		0x80	// if set in attributes, block cannot be moved
+#define PURGEBITS	3		// 0-3 level, 0= unpurgable, 3= purge first
+#define PURGEMASK	0xfffc
+#define BASEATTRIBUTES	0	// unlocked, non purgable
+
+#define MAXUMBS		10
+
+typedef struct mmblockstruct
+{
+	unsigned	start,length;
+	unsigned	attributes;
+	memptr		*useptr;	// pointer to the segment start
+	struct mmblockstruct far *next;
+} mmblocktype;
+
+
+//#define GETNEWBLOCK {if(!(mmnew=mmfree))Quit("MM_GETNEWBLOCK: No free blocks!")\
+//	;mmfree=mmfree->next;}
+
+#define GETNEWBLOCK {if(!mmfree)MML_ClearBlock();mmnew=mmfree;mmfree=mmfree->next;}
+
+#define FREEBLOCK(x) {*x->useptr=NULL;x->next=mmfree;mmfree=x;}
+
+/*
+=============================================================================
+
+						 GLOBAL VARIABLES
+
+=============================================================================
+*/
+
+mminfotype	mminfo;
+memptr		bufferseg;
+boolean		mmerror;
+
+void		(* beforesort) (void);
+void		(* aftersort) (void);
+
+/*
+=============================================================================
+
+						 LOCAL VARIABLES
+
+=============================================================================
+*/
+
+boolean		mmstarted;
+
+void far	*farheap;
+void		*nearheap;
+
+mmblocktype	far mmblocks[MAXBLOCKS]
+			,far *mmhead,far *mmfree,far *mmrover,far *mmnew;
+
+boolean		bombonerror;
+
+unsigned	totalEMSpages,freeEMSpages,EMSpageframe,EMSpagesmapped,EMShandle;
+
+void		(* XMSaddr) (void);		// far pointer to XMS driver
+
+unsigned	numUMBs,UMBbase[MAXUMBS];
+
+//==========================================================================
+
+//
+// local prototypes
+//
+
+boolean		MML_CheckForEMS (void);
+void 		MML_ShutdownEMS (void);
+void 		MM_MapEMS (void);
+boolean 	MML_CheckForXMS (void);
+void 		MML_ShutdownXMS (void);
+void		MML_UseSpace (unsigned segstart, unsigned seglength);
+void 		MML_ClearBlock (void);
+
+//==========================================================================
+
+/*
+======================
+=
+= MML_CheckForEMS
+=
+= Routine from p36 of Extending DOS
+=
+=======================
+*/
+
+char	emmname[9] = "EMMXXXX0";
+
+boolean MML_CheckForEMS (void)
+{
+asm	mov	dx,OFFSET emmname[0]
+asm	mov	ax,0x3d00
+asm	int	0x21		// try to open EMMXXXX0 device
+asm	jc	error
+
+asm	mov	bx,ax
+asm	mov	ax,0x4400
+
+asm	int	0x21		// get device info
+asm	jc	error
+
+asm	and	dx,0x80
+asm	jz	error
+
+asm	mov	ax,0x4407
+
+asm	int	0x21		// get status
+asm	jc	error
+asm	or	al,al
+asm	jz	error
+
+asm	mov	ah,0x3e
+asm	int	0x21		// close handle
+asm	jc	error
+
+//
+// EMS is good
+//
+  return true;
+
+error:
+//
+// EMS is bad
+//
+  return false;
+}
+
+
+/*
+======================
+=
+= MML_SetupEMS
+=
+=======================
+*/
+
+void MML_SetupEMS (void)
+{
+	char	str[80],str2[10];
+	unsigned	error;
+
+	totalEMSpages = freeEMSpages = EMSpageframe = EMSpagesmapped = 0;
+
+asm {
+	mov	ah,EMS_STATUS
+	int	EMS_INT						// make sure EMS hardware is present
+	or	ah,ah
+	jnz	error
+
+	mov	ah,EMS_VERSION
+	int	EMS_INT
+	or	ah,ah
+	jnz	error
+	cmp	al,0x32						// only work on ems 3.2 or greater
+	jb	error
+
+	mov	ah,EMS_GETFRAME
+	int	EMS_INT						// find the page frame address
+	or	ah,ah
+	jnz	error
+	mov	[EMSpageframe],bx
+
+	mov	ah,EMS_GETPAGES
+	int	EMS_INT						// find out how much EMS is there
+	or	ah,ah
+	jnz	error
+	mov	[totalEMSpages],dx
+	mov	[freeEMSpages],bx
+	or	bx,bx
+	jz	noEMS						// no EMS at all to allocate
+
+	cmp	bx,4
+	jle	getpages					// there is only 1,2,3,or 4 pages
+	mov	bx,4						// we can't use more than 4 pages
+	}
+
+getpages:
+asm {
+	mov	[EMSpagesmapped],bx
+	mov	ah,EMS_ALLOCPAGES			// allocate up to 64k of EMS
+	int	EMS_INT
+	or	ah,ah
+	jnz	error
+	mov	[EMShandle],dx
+	}
+	return;
+
+error:
+	error = _AH;
+	strcpy (str,"MML_SetupEMS: EMS error 0x");
+	itoa(error,str2,16);
+	strcpy (str,str2);
+	Quit (str);
+
+noEMS:
+;
+}
+
+
+/*
+======================
+=
+= MML_ShutdownEMS
+=
+=======================
+*/
+
+void MML_ShutdownEMS (void)
+{
+	if (!EMShandle)
+		return;
+
+asm	{
+	mov	ah,EMS_FREEPAGES
+	mov	dx,[EMShandle]
+	int	EMS_INT
+	or	ah,ah
+	jz	ok
+	}
+
+	Quit ("MML_ShutdownEMS: Error freeing EMS!");
+
+ok:
+;
+}
+
+/*
+====================
+=
+= MM_MapEMS
+=
+= Maps the 64k of EMS used by memory manager into the page frame
+= for general use.  This only needs to be called if you are keeping
+= other things in EMS.
+=
+====================
+*/
+
+void MM_MapEMS (void)
+{
+	char	str[80],str2[10];
+	unsigned	error;
+	int	i;
+
+	for (i=0;i<EMSpagesmapped;i++)
+	{
+	asm	{
+		mov	ah,EMS_MAPPAGE
+		mov	bx,[i]			// logical page
+		mov	al,bl			// physical page
+		mov	dx,[EMShandle]	// handle
+		int	EMS_INT
+		or	ah,ah
+		jnz	error
+		}
+	}
+
+	return;
+
+error:
+	error = _AH;
+	strcpy (str,"MM_MapEMS: EMS error 0x");
+	itoa(error,str2,16);
+	strcpy (str,str2);
+	Quit (str);
+}
+
+//==========================================================================
+
+/*
+======================
+=
+= MML_CheckForXMS
+=
+= Check for XMM driver
+=
+=======================
+*/
+
+boolean MML_CheckForXMS (void)
+{
+	numUMBs = 0;
+
+asm {
+	mov	ax,0x4300
+	int	0x2f				// query status of installed diver
+	cmp	al,0x80
+	je	good
+	}
+	return false;
+good:
+	return true;
+}
+
+
+/*
+======================
+=
+= MML_SetupXMS
+=
+= Try to allocate all upper memory block
+=
+=======================
+*/
+
+void MML_SetupXMS (void)
+{
+	unsigned	base,size;
+
+asm	{
+	mov	ax,0x4310
+	int	0x2f
+	mov	[WORD PTR XMSaddr],bx
+	mov	[WORD PTR XMSaddr+2],es		// function pointer to XMS driver
+	}
+
+getmemory:
+asm	{
+	mov	ah,XMS_ALLOCUMB
+	mov	dx,0xffff					// try for largest block possible
+	call	[DWORD PTR XMSaddr]
+	or	ax,ax
+	jnz	gotone
+
+	cmp	bl,0xb0						// error: smaller UMB is available
+	jne	done;
+
+	mov	ah,XMS_ALLOCUMB
+	call	[DWORD PTR XMSaddr]		// DX holds largest available UMB
+	or	ax,ax
+	jz	done						// another error...
+	}
+
+gotone:
+asm	{
+	mov	[base],bx
+	mov	[size],dx
+	}
+	MML_UseSpace (base,size);
+	mminfo.XMSmem += size*16;
+	UMBbase[numUMBs] = base;
+	numUMBs++;
+	if (numUMBs < MAXUMBS)
+		goto getmemory;
+
+done:;
+}
+
+
+/*
+======================
+=
+= MML_ShutdownXMS
+=
+======================
+*/
+
+void MML_ShutdownXMS (void)
+{
+	int	i;
+	unsigned	base;
+
+	for (i=0;i<numUMBs;i++)
+	{
+		base = UMBbase[i];
+
+asm	mov	ah,XMS_FREEUMB
+asm	mov	dx,[base]
+asm	call	[DWORD PTR XMSaddr]
+	}
+}
+
+//==========================================================================
+
+/*
+======================
+=
+= MML_UseSpace
+=
+= Marks a range of paragraphs as usable by the memory manager
+= This is used to mark space for the near heap, far heap, ems page frame,
+= and upper memory blocks
+=
+======================
+*/
+
+void MML_UseSpace (unsigned segstart, unsigned seglength)
+{
+	mmblocktype far *scan,far *last;
+	unsigned	oldend;
+	long		extra;
+
+	scan = last = mmhead;
+	mmrover = mmhead;		// reset rover to start of memory
+
+//
+// search for the block that contains the range of segments
+//
+	while (scan->start+scan->length < segstart)
+	{
+		last = scan;
+		scan = scan->next;
+	}
+
+//
+// take the given range out of the block
+//
+	oldend = scan->start + scan->length;
+	extra = oldend - (segstart+seglength);
+	if (extra < 0)
+		Quit ("MML_UseSpace: Segment spans two blocks!");
+
+	if (segstart == scan->start)
+	{
+		last->next = scan->next;			// unlink block
+		FREEBLOCK(scan);
+		scan = last;
+	}
+	else
+		scan->length = segstart-scan->start;	// shorten block
+
+	if (extra > 0)
+	{
+		GETNEWBLOCK;
+		mmnew->useptr = NULL;			// Keen addition
+
+		mmnew->next = scan->next;
+		scan->next = mmnew;
+		mmnew->start = segstart+seglength;
+		mmnew->length = extra;
+		mmnew->attributes = LOCKBIT;
+	}
+
+}
+
+//==========================================================================
+
+/*
+====================
+=
+= MML_ClearBlock
+=
+= We are out of blocks, so free a purgable block
+=
+====================
+*/
+
+void MML_ClearBlock (void)
+{
+	mmblocktype far *scan,far *last;
+
+	scan = mmhead->next;
+
+	while (scan)
+	{
+		if (!(scan->attributes&LOCKBIT) && (scan->attributes&PURGEBITS) )
+		{
+			MM_FreePtr(scan->useptr);
+			return;
+		}
+		scan = scan->next;
+	}
+
+	Quit ("MM_ClearBlock: No purgable blocks!");
+}
+
+
+//==========================================================================
+
+/*
+===================
+=
+= MM_Startup
+=
+= Grabs all space from turbo with malloc/farmalloc
+= Allocates bufferseg misc buffer
+=
+===================
+*/
+
+static	char *ParmStrings[] = {"noems","noxms",""};
+
+void MM_Startup (void)
+{
+	int i;
+	unsigned 	long length;
+	void far 	*start;
+	unsigned 	segstart,seglength,endfree;
+
+	if (mmstarted)
+		MM_Shutdown ();
+
+
+	mmstarted = true;
+	bombonerror = true;
+//
+// set up the linked list (everything in the free list;
+//
+	mmhead = NULL;
+	mmfree = &mmblocks[0];
+	for (i=0;i<MAXBLOCKS-1;i++)
+		mmblocks[i].next = &mmblocks[i+1];
+	mmblocks[i].next = NULL;
+
+//
+// locked block of all memory until we punch out free space
+//
+	GETNEWBLOCK;
+	mmhead = mmnew;				// this will allways be the first node
+	mmnew->start = 0;
+	mmnew->length = 0xffff;
+	mmnew->attributes = LOCKBIT;
+	mmnew->next = NULL;
+	mmrover = mmhead;
+
+
+//
+// get all available near conventional memory segments
+//
+	length=coreleft();
+	start = (void far *)(nearheap = malloc(length));
+
+	length -= 16-(FP_OFF(start)&15);
+	length -= SAVENEARHEAP;
+	seglength = length / 16;			// now in paragraphs
+	segstart = FP_SEG(start)+(FP_OFF(start)+15)/16;
+	MML_UseSpace (segstart,seglength);
+	mminfo.nearheap = length;
+
+//
+// get all available far conventional memory segments
+//
+	length=farcoreleft();
+	start = farheap = farmalloc(length);
+	length -= 16-(FP_OFF(start)&15);
+	length -= SAVEFARHEAP;
+	seglength = length / 16;			// now in paragraphs
+	segstart = FP_SEG(start)+(FP_OFF(start)+15)/16;
+	MML_UseSpace (segstart,seglength);
+	mminfo.farheap = length;
+	mminfo.mainmem = mminfo.nearheap + mminfo.farheap;
+
+
+//
+// detect EMS and allocate up to 64K at page frame
+//
+	mminfo.EMSmem = 0;
+	for (i = 1;i < _argc;i++)
+	{
+		if ( US_CheckParm(_argv[i],ParmStrings) == 0)
+			goto emsskip;				// param NOEMS
+	}
+
+	if (MML_CheckForEMS())
+	{
+		MML_SetupEMS();					// allocate space
+		MML_UseSpace (EMSpageframe,EMSpagesmapped*0x400);
+		MM_MapEMS();					// map in used pages
+		mminfo.EMSmem = EMSpagesmapped*0x4000l;
+	}
+
+//
+// detect XMS and get upper memory blocks
+//
+emsskip:
+	mminfo.XMSmem = 0;
+	for (i = 1;i < _argc;i++)
+	{
+		if ( US_CheckParm(_argv[i],ParmStrings) == 0)	// BUG: NOXMS is index 1, not 0
+			goto xmsskip;				// param NOXMS
+	}
+
+	if (MML_CheckForXMS())
+		MML_SetupXMS();					// allocate as many UMBs as possible
+
+//
+// allocate the misc buffer
+//
+xmsskip:
+	mmrover = mmhead;		// start looking for space after low block
+
+	MM_GetPtr (&bufferseg,BUFFERSIZE);
+}
+
+//==========================================================================
+
+/*
+====================
+=
+= MM_Shutdown
+=
+= Frees all conventional, EMS, and XMS allocated
+=
+====================
+*/
+
+void MM_Shutdown (void)
+{
+  if (!mmstarted)
+	return;
+
+  farfree (farheap);
+  free (nearheap);
+  MML_ShutdownEMS ();
+  MML_ShutdownXMS ();
+}
+
+//==========================================================================
+
+/*
+====================
+=
+= MM_GetPtr
+=
+= Allocates an unlocked, unpurgable block
+=
+====================
+*/
+
+void MM_GetPtr (memptr *baseptr,unsigned long size)
+{
+	mmblocktype far *scan,far *lastscan,far *endscan
+				,far *purge,far *next;
+	int			search;
+	unsigned	needed,startseg;
+
+	needed = (size+15)/16;		// convert size from bytes to paragraphs
+
+	GETNEWBLOCK;				// fill in start and next after a spot is found
+	mmnew->length = needed;
+	mmnew->useptr = baseptr;
+	mmnew->attributes = BASEATTRIBUTES;
+
+	for (search = 0; search<3; search++)
+	{
+	//
+	// first search:	try to allocate right after the rover, then on up
+	// second search: 	search from the head pointer up to the rover
+	// third search:	compress memory, then scan from start
+		if (search == 1 && mmrover == mmhead)
+			search++;
+
+		switch (search)
+		{
+		case 0:
+			lastscan = mmrover;
+			scan = mmrover->next;
+			endscan = NULL;
+			break;
+		case 1:
+			lastscan = mmhead;
+			scan = mmhead->next;
+			endscan = mmrover;
+			break;
+		case 2:
+			MM_SortMem ();
+			lastscan = mmhead;
+			scan = mmhead->next;
+			endscan = NULL;
+			break;
+		}
+
+		startseg = lastscan->start + lastscan->length;
+
+		while (scan != endscan)
+		{
+			if (scan->start - startseg >= needed)
+			{
+			//
+			// got enough space between the end of lastscan and
+			// the start of scan, so throw out anything in the middle
+			// and allocate the new block
+			//
+				purge = lastscan->next;
+				lastscan->next = mmnew;
+				mmnew->start = *(unsigned *)baseptr = startseg;
+				mmnew->next = scan;
+				while ( purge != scan)
+				{	// free the purgable block
+					next = purge->next;
+					FREEBLOCK(purge);
+					purge = next;		// purge another if not at scan
+				}
+				mmrover = mmnew;
+				return;	// good allocation!
+			}
+
+			//
+			// if this block is purge level zero or locked, skip past it
+			//
+			if ( (scan->attributes & LOCKBIT)
+				|| !(scan->attributes & PURGEBITS) )
+			{
+				lastscan = scan;
+				startseg = lastscan->start + lastscan->length;
+			}
+
+
+			scan=scan->next;		// look at next line
+		}
+	}
+
+	if (bombonerror)
+		Quit ("MM_GetPtr: Out of memory!");
+	else
+		mmerror = true;
+}
+
+//==========================================================================
+
+/*
+====================
+=
+= MM_FreePtr
+=
+= Allocates an unlocked, unpurgable block
+=
+====================
+*/
+
+void MM_FreePtr (memptr *baseptr)
+{
+	mmblocktype far *scan,far *last;
+
+	last = mmhead;
+	scan = last->next;
+
+	if (baseptr == mmrover->useptr)	// removed the last allocated block
+		mmrover = mmhead;
+
+	while (scan->useptr != baseptr && scan)
+	{
+		last = scan;
+		scan = scan->next;
+	}
+
+	if (!scan)
+		Quit ("MM_FreePtr: Block not found!");
+
+	last->next = scan->next;
+
+	FREEBLOCK(scan);
+}
+//==========================================================================
+
+/*
+=====================
+=
+= MM_SetPurge
+=
+= Sets the purge level for a block (locked blocks cannot be made purgable)
+=
+=====================
+*/
+
+void MM_SetPurge (memptr *baseptr, int purge)
+{
+	mmblocktype far *start;
+
+	start = mmrover;
+
+	do
+	{
+		if (mmrover->useptr == baseptr)
+			break;
+
+		mmrover = mmrover->next;
+
+		if (!mmrover)
+			mmrover = mmhead;
+		else if (mmrover == start)
+			Quit ("MM_SetPurge: Block not found!");
+
+	} while (1);
+
+	mmrover->attributes &= ~PURGEBITS;
+	mmrover->attributes |= purge;
+}
+
+//==========================================================================
+
+/*
+=====================
+=
+= MM_SetLock
+=
+= Locks / unlocks the block
+=
+=====================
+*/
+
+void MM_SetLock (memptr *baseptr, boolean locked)
+{
+	mmblocktype far *start;
+
+	start = mmrover;
+
+	do
+	{
+		if (mmrover->useptr == baseptr)
+			break;
+
+		mmrover = mmrover->next;
+
+		if (!mmrover)
+			mmrover = mmhead;
+		else if (mmrover == start)
+			Quit ("MM_SetLock: Block not found!");
+
+	} while (1);
+
+	mmrover->attributes &= ~LOCKBIT;
+	mmrover->attributes |= locked*LOCKBIT;
+}
+
+//==========================================================================
+
+/*
+=====================
+=
+= MM_SortMem
+=
+= Throws out all purgable stuff and compresses movable blocks
+=
+=====================
+*/
+
+void MM_SortMem (void)
+{
+	mmblocktype far *scan,far *last,far *next;
+	unsigned	start,length,source,dest,oldborder;
+	int			playing;
+
+	//
+	// lock down a currently playing sound
+	//
+	playing = SD_SoundPlaying ();
+	if (playing)
+	{
+		switch (SoundMode)
+		{
+		case sdm_PC:
+			playing += STARTPCSOUNDS;
+			break;
+		case sdm_AdLib:
+			playing += STARTADLIBSOUNDS;
+			break;
+		}
+		MM_SetLock(&(memptr)audiosegs[playing],true);
+	}
+
+
+	SD_StopSound();
+	oldborder = bordercolor;
+	VW_ColorBorder (15);
+
+	if (beforesort)
+		beforesort();
+
+	scan = mmhead;
+
+	last = NULL;		// shut up compiler warning
+
+	while (scan)
+	{
+		if (scan->attributes & LOCKBIT)
+		{
+		//
+		// block is locked, so try to pile later blocks right after it
+		//
+			start = scan->start + scan->length;
+		}
+		else
+		{
+			if (scan->attributes & PURGEBITS)
+			{
+			//
+			// throw out the purgable block
+			//
+				next = scan->next;
+				FREEBLOCK(scan);
+				last->next = next;
+				scan = next;
+				continue;
+			}
+			else
+			{
+			//
+			// push the non purgable block on top of the last moved block
+			//
+				if (scan->start != start)
+				{
+					length = scan->length;
+					source = scan->start;
+					dest = start;
+					while (length > 0xf00)
+					{
+						movedata(source,0,dest,0,0xf00*16);
+						length -= 0xf00;
+						source += 0xf00;
+						dest += 0xf00;
+					}
+					movedata(source,0,dest,0,length*16);
+
+					scan->start = start;
+					*(unsigned *)scan->useptr = start;
+				}
+				start = scan->start + scan->length;
+			}
+		}
+
+		last = scan;
+		scan = scan->next;		// go to next block
+	}
+
+	mmrover = mmhead;
+
+	if (aftersort)
+		aftersort();
+
+	VW_ColorBorder (oldborder);
+
+	if (playing)
+		MM_SetLock(&(memptr)audiosegs[playing],false);
+}
+
+
+//==========================================================================
+
+/*
+=====================
+=
+= MM_ShowMemory
+=
+=====================
+*/
+
+void MM_ShowMemory (void)
+{
+	mmblocktype far *scan;
+	unsigned color,temp;
+	long	end,owner;
+	char    scratch[80],str[10];
+
+	VW_SetDefaultColors();
+	VW_SetLineWidth(40);
+	temp = bufferofs;
+	bufferofs = 0;
+	VW_SetScreen (0,0);
+
+	scan = mmhead;
+
+	end = -1;
+
+//CA_OpenDebug ();
+
+	while (scan)
+	{
+		if (scan->attributes & PURGEBITS)
+			color = 5;		// dark purple = purgable
+		else
+			color = 9;		// medium blue = non purgable
+		if (scan->attributes & LOCKBIT)
+			color = 12;		// red = locked
+		if (scan->start<=end)
+			Quit ("MM_ShowMemory: Memory block order corrupted!");
+		end = scan->start+scan->length-1;
+		VW_Hlin(scan->start,(unsigned)end,0,color);
+		VW_Plot(scan->start,0,15);
+		if (scan->next->start > end+1)
+			VW_Hlin(end+1,scan->next->start,0,0);	// black = free
+
+#if 0
+strcpy (scratch,"Size:");
+ltoa ((long)scan->length*16,str,10);
+strcat (scratch,str);
+strcat (scratch,"\tOwner:0x");
+owner = (unsigned)scan->useptr;
+ultoa (owner,str,16);
+strcat (scratch,str);
+strcat (scratch,"\n");
+write (debughandle,scratch,strlen(scratch));
+#endif
+
+		scan = scan->next;
+	}
+
+//CA_CloseDebug ();
+
+	IN_Ack();
+	VW_SetLineWidth(64);
+	bufferofs = temp;
+}
+
+//==========================================================================
+
+
+/*
+======================
+=
+= MM_UnusedMemory
+=
+= Returns the total free space without purging
+=
+======================
+*/
+
+long MM_UnusedMemory (void)
+{
+	unsigned free;
+	mmblocktype far *scan;
+
+	free = 0;
+	scan = mmhead;
+
+	while (scan->next)
+	{
+		free += scan->next->start - (scan->start + scan->length);
+		scan = scan->next;
+	}
+
+	return free*16l;
+}
+
+//==========================================================================
+
+
+/*
+======================
+=
+= MM_TotalFree
+=
+= Returns the total free space with purging
+=
+======================
+*/
+
+long MM_TotalFree (void)
+{
+	unsigned free;
+	mmblocktype far *scan;
+
+	free = 0;
+	scan = mmhead;
+
+	while (scan->next)
+	{
+		if ((scan->attributes&PURGEBITS) && !(scan->attributes&LOCKBIT))
+			free += scan->length;
+		free += scan->next->start - (scan->start + scan->length);
+		scan = scan->next;
+	}
+
+	return free*16l;
+}
+
+//==========================================================================
+
+/*
+=====================
+=
+= MM_BombOnError
+=
+=====================
+*/
+
+void MM_BombOnError (boolean bomb)
+{
+	bombonerror = bomb;
+}
+
+
diff --git a/16/keen456/KEEN4-6/ID_MM.H b/16/keen456/KEEN4-6/ID_MM.H
new file mode 100755
index 00000000..4cf2d169
--- /dev/null
+++ b/16/keen456/KEEN4-6/ID_MM.H
@@ -0,0 +1,116 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+// ID_MM.H
+
+#ifndef __ID_CA__
+
+#define __ID_CA__
+
+#define SAVENEARHEAP	0x400		// space to leave in data segment
+#define SAVEFARHEAP		0			// space to leave in far heap
+
+#define	BUFFERSIZE		0x1000		// miscelanious, allways available buffer
+
+#ifdef CAT3D
+#define MAXBLOCKS		600
+#else
+#define MAXBLOCKS		1200
+#endif
+
+
+//--------
+
+#define	EMS_INT			0x67
+
+#define	EMS_STATUS		0x40
+#define	EMS_GETFRAME	0x41
+#define	EMS_GETPAGES	0x42
+#define	EMS_ALLOCPAGES	0x43
+#define	EMS_MAPPAGE		0x44
+#define	EMS_FREEPAGES	0x45
+#define	EMS_VERSION		0x46
+
+//--------
+
+#define	XMS_VERSION		0x00
+
+#define	XMS_ALLOCHMA	0x01
+#define	XMS_FREEHMA		0x02
+
+#define	XMS_GENABLEA20	0x03
+#define	XMS_GDISABLEA20	0x04
+#define	XMS_LENABLEA20	0x05
+#define	XMS_LDISABLEA20	0x06
+#define	XMS_QUERYA20	0x07
+
+#define	XMS_QUERYREE	0x08
+#define	XMS_ALLOC		0x09
+#define	XMS_FREE		0x0A
+#define	XMS_MOVE		0x0B
+#define	XMS_LOCK		0x0C
+#define	XMS_UNLOCK		0x0D
+#define	XMS_GETINFO		0x0E
+#define	XMS_RESIZE		0x0F
+
+#define	XMS_ALLOCUMB	0x10
+#define	XMS_FREEUMB		0x11
+
+//==========================================================================
+
+typedef void _seg * memptr;
+
+typedef struct
+{
+	long	nearheap,farheap,EMSmem,XMSmem,mainmem;
+} mminfotype;
+
+//==========================================================================
+
+extern	mminfotype	mminfo;
+extern	memptr		bufferseg;
+extern	boolean		mmerror;
+
+extern	void		(* beforesort) (void);
+extern	void		(* aftersort) (void);
+
+//==========================================================================
+
+void MM_Startup (void);
+void MM_Shutdown (void);
+void MM_MapEMS (void);
+
+void MM_GetPtr (memptr *baseptr,unsigned long size);
+void MM_FreePtr (memptr *baseptr);
+
+void MM_SetPurge (memptr *baseptr, int purge);
+void MM_SetLock (memptr *baseptr, boolean locked);
+void MM_SortMem (void);
+
+void MM_ShowMemory (void);
+
+long MM_UnusedMemory (void);
+long MM_TotalFree (void);
+
+void MM_BombOnError (boolean bomb);
+
+#endif
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/ID_RF.C b/16/keen456/KEEN4-6/ID_RF.C
new file mode 100755
index 00000000..a040c6bf
--- /dev/null
+++ b/16/keen456/KEEN4-6/ID_RF.C
@@ -0,0 +1,2965 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+// ID_RF.C
+
+/*
+=============================================================================
+
+notes
+-----
+
+scrolling more than one tile / refresh forces a total redraw
+
+two overlapping sprites of equal priority can change drawing order when
+updated
+
+=============================================================================
+*/
+
+#include "ID_HEADS.H"
+#pragma hdrstop
+
+/*
+=============================================================================
+
+						 LOCAL CONSTANTS
+
+=============================================================================
+*/
+
+#define	SCREENTILESWIDE	20
+#define	SCREENTILESHIGH	13
+
+#define	SCREENSPACE		(SCREENWIDTH*240)
+#define FREEEGAMEM		(0x10000l-3l*SCREENSPACE)
+
+//
+// the update array must have enough space for two screens that can float
+// up two two tiles each way
+//
+// (PORTTILESWIDE+1)*PORTTILESHIGH must be even so the arrays can be cleared
+// by word width instructions
+
+#define	UPDATESCREENSIZE	(UPDATEWIDE*PORTTILESHIGH+2)
+#define	UPDATESPARESIZE		(UPDATEWIDE*2+4)
+#define UPDATESIZE			(UPDATESCREENSIZE+2*UPDATESPARESIZE)
+
+#define G_EGASX_SHIFT	7	// global >> ?? = screen x
+#define G_CGASX_SHIFT	6	// global >> ?? = screen x
+#define G_SY_SHIFT		4	// global >> ?? = screen y
+
+unsigned	SX_T_SHIFT;		// screen x >> ?? = tile EGA = 1, CGA = 2;
+#define	SY_T_SHIFT		4	// screen y >> ?? = tile
+
+
+#define	EGAPORTSCREENWIDE	42
+#define	CGAPORTSCREENWIDE	84
+#define	PORTSCREENHIGH		224
+
+#define	UPDATESCREENSIZE	(UPDATEWIDE*PORTTILESHIGH+2)
+#define	UPDATESPARESIZE		(UPDATEWIDE*2+4)
+#define UPDATESIZE			(UPDATESCREENSIZE+2*UPDATESPARESIZE)
+
+#define MAXSCROLLEDGES	6
+
+/*
+=============================================================================
+
+						   LOCAL TYPES
+
+=============================================================================
+*/
+
+typedef	struct spriteliststruct
+{
+	int			screenx,screeny;
+	int			width,height;
+
+	unsigned	grseg,sourceofs,planesize;
+	drawtype	draw;
+	unsigned	tilex,tiley,tilewide,tilehigh;
+	int			priority,updatecount;
+	struct spriteliststruct **prevptr,*nextsprite;
+} spritelisttype;
+
+
+typedef struct
+{
+	int			screenx,screeny;
+	int			width,height;
+} eraseblocktype;
+
+
+typedef struct
+{
+	unsigned	current;		// foreground tiles have high bit set
+	int			count;
+#ifdef KEEN6
+	unsigned	soundtile;
+	unsigned	visible;
+	int		sound;
+#endif
+} tiletype;
+
+
+typedef struct animtilestruct
+{
+	unsigned	x,y,tile;
+	tiletype	*chain;
+	unsigned	far *mapplane;
+	struct animtilestruct **prevptr,*nexttile;
+} animtiletype;
+
+/*
+=============================================================================
+
+						 GLOBAL VARIABLES
+
+=============================================================================
+*/
+
+unsigned	tics;
+long		lasttimecount;
+
+boolean		compatability;			// crippled refresh for wierdo SVGAs
+
+unsigned	mapwidth,mapheight,mapbyteswide,mapwordswide
+			,mapbytesextra,mapwordsextra;
+unsigned	mapbwidthtable[MAXMAPHEIGHT];
+
+//
+// Global : Actor coordinates are in this, at 1/16 th of a pixel, to allow
+// for fractional movement and acceleration.
+//
+// Tiles  : Tile offsets from the upper left corner of the current map.
+//
+// Screen : Graphics level offsets from map origin, x in bytes, y in pixels.
+// originxscreen is the same spot as originxtile, just with extra precision
+// so graphics don't need to be done in tile boundaries.
+//
+
+unsigned	originxglobal,originyglobal;
+unsigned	originxtile,originytile;
+unsigned	originxscreen,originyscreen;
+unsigned	originmap;
+unsigned	originxmin,originxmax,originymin,originymax;
+
+unsigned	masterofs;
+
+//
+// Table of the offsets from bufferofs of each tile spot in the
+// view port.  The extra wide tile should never be drawn, but the space
+// is needed to account for the extra 0 in the update arrays.  Built by
+// RF_Startup
+//
+
+unsigned	blockstarts[UPDATEWIDE*UPDATEHIGH];
+unsigned	updatemapofs[UPDATEWIDE*UPDATEHIGH];
+
+unsigned	uwidthtable[PORTTILESHIGH];		// lookup instead of multiply
+
+byte		update[2][UPDATESIZE];
+byte		*updateptr,*baseupdateptr,						// current start of update window
+			*updatestart[2],
+			*baseupdatestart[2];
+
+/*
+=============================================================================
+
+						 LOCAL VARIABLES
+
+=============================================================================
+*/
+
+static		char	scratch[20],str[80];
+
+tiletype	allanims[MAXANIMTYPES];
+unsigned	numanimchains;
+
+void 		(*refreshvector) (void);
+
+unsigned	screenstart[3] =
+	{0,SCREENSPACE,SCREENSPACE*2};
+
+unsigned	xpanmask;			// prevent panning to odd pixels
+
+unsigned	screenpage;			// screen currently being displayed
+unsigned	otherpage;
+
+
+spritelisttype	spritearray[MAXSPRITES],*prioritystart[PRIORITIES],
+				*spritefreeptr;
+
+animtiletype	animarray[MAXANIMTILES],*animhead,*animfreeptr;
+
+int				animfreespot;
+
+eraseblocktype	eraselist[2][MAXSPRITES],*eraselistptr[2];
+
+int		hscrollblocks,vscrollblocks;
+int		hscrolledge[MAXSCROLLEDGES],vscrolledge[MAXSCROLLEDGES];
+
+/*
+=============================================================================
+
+						 LOCAL PROTOTYPES
+
+=============================================================================
+*/
+
+void RFL_NewTile (unsigned updateoffset);
+void RFL_MaskForegroundTiles (void);
+void RFL_UpdateTiles (void);
+
+void RFL_BoundScroll (int x, int y);
+void RFL_CalcOriginStuff (long x, long y);
+void RFL_ClearScrollBlocks (void);
+void RFL_InitSpriteList (void);
+void RFL_InitAnimList (void);
+void RFL_CheckForAnimTile (unsigned x, unsigned y);
+void RFL_AnimateTiles (void);
+void RFL_RemoveAnimsOnX (unsigned x);
+void RFL_RemoveAnimsOnY (unsigned y);
+void RFL_EraseBlocks (void);
+void RFL_UpdateSprites (void);
+
+
+/*
+=============================================================================
+
+					 GRMODE INDEPENDANT ROUTINES
+
+=============================================================================
+*/
+
+
+/*
+=====================
+=
+= RF_Startup
+=
+=====================
+*/
+
+static	char *ParmStrings[] = {"comp",""};
+
+void RF_Startup (void)
+{
+	int i,x,y;
+	unsigned	*blockstart;
+
+#ifndef KEEN
+	//
+	// Keen 4-6 store the compatability setting in the game's config file.
+	// The setting is loaded from that file AFTER RF_Startup is executed,
+	// making this check useless (unless the config file doesn't exist).
+	// Instead, US_Startup now checks for that parameter after the config
+	// file has been read.
+	//
+	if (grmode == EGAGR)
+		for (i = 1;i < _argc;i++)
+			if (US_CheckParm(_argv[i],ParmStrings) == 0)
+			{
+				compatability = true;
+				break;
+			}
+#endif
+
+	for (i=0;i<PORTTILESHIGH;i++)
+		uwidthtable[i] = UPDATEWIDE*i;
+
+	originxmin = originymin = MAPBORDER*TILEGLOBAL;
+
+	eraselistptr[0] = &eraselist[0][0];
+	eraselistptr[1] = &eraselist[1][0];
+
+
+
+	if (grmode == EGAGR)
+	{
+		SX_T_SHIFT = 1;
+
+		baseupdatestart[0] = &update[0][UPDATESPARESIZE];
+		baseupdatestart[1] = &update[1][UPDATESPARESIZE];
+
+		screenpage = 0;
+		otherpage = 1;
+		displayofs = screenstart[screenpage];
+		bufferofs = screenstart[otherpage];
+		masterofs = screenstart[2];
+
+		updateptr = baseupdatestart[otherpage];
+
+		blockstart = &blockstarts[0];
+		for (y=0;y<UPDATEHIGH;y++)
+			for (x=0;x<UPDATEWIDE;x++)
+				*blockstart++ = SCREENWIDTH*16*y+x*TILEWIDTH;
+
+		xpanmask = 6;	// dont pan to odd pixels
+	}
+
+	else if (grmode == CGAGR)
+	{
+		SX_T_SHIFT = 2;
+
+		updateptr = baseupdateptr = &update[0][UPDATESPARESIZE];
+
+		bufferofs = 0;
+		masterofs = 0x8000;
+
+		blockstart = &blockstarts[0];
+		for (y=0;y<UPDATEHIGH;y++)
+			for (x=0;x<UPDATEWIDE;x++)
+				*blockstart++ = SCREENWIDTH*16*y+x*TILEWIDTH;
+	}
+}
+
+
+
+
+/*
+=====================
+=
+= RF_Shutdown
+=
+=====================
+*/
+
+void RF_Shutdown (void)
+{
+
+}
+
+//===========================================================================
+
+
+/*
+=====================
+=
+= RF_FixOfs
+=
+= Sets bufferofs,displayofs, and masterofs to regular values, for the
+= occasions when you have moved them around manually
+=
+=====================
+*/
+
+void RF_FixOfs (void)
+{
+	screenstart[0] = 0;
+	screenstart[1] = SCREENSPACE;
+	screenstart[2] = SCREENSPACE*2;
+
+	if (grmode == EGAGR)
+	{
+		screenpage = 0;
+		otherpage = 1;
+		panx = pany = pansx = pansy = panadjust = 0;
+		displayofs = screenstart[screenpage];
+		bufferofs = screenstart[otherpage];
+		masterofs = screenstart[2];
+		VW_SetScreen (displayofs,0);
+	}
+	else
+	{
+		panx = pany = pansx = pansy = panadjust = 0;
+		bufferofs = 0;
+		masterofs = 0x8000;
+	}
+}
+
+
+//===========================================================================
+
+/*
+=====================
+=
+= RF_NewMap
+=
+= Makes some convienient calculations based on maphead->
+=
+=====================
+*/
+
+void RF_NewMap (void)
+{
+	int i,x,y;
+	unsigned spot,*table;
+
+	mapwidth = mapheaderseg[mapon]->width;
+	mapbyteswide = 2*mapwidth;
+	mapheight = mapheaderseg[mapon]->height;
+	mapwordsextra = mapwidth-PORTTILESWIDE;
+	mapbytesextra = 2*mapwordsextra;
+
+//
+// make a lookup table for the maps left edge
+//
+	if (mapheight > MAXMAPHEIGHT)
+		Quit ("RF_NewMap: Map too tall!");
+	spot = 0;
+	for (i=0;i<mapheight;i++)
+	{
+	  mapbwidthtable[i] = spot;
+	  spot += mapbyteswide;
+	}
+
+//
+// fill in updatemapofs with the new width info
+//
+	table = &updatemapofs[0];
+	for (y=0;y<PORTTILESHIGH;y++)
+		for (x=0;x<UPDATEWIDE;x++)
+			*table++ = mapbwidthtable[y]+x*2;
+
+//
+// the y max value clips off the bottom half of a tile so a map that is
+// 13 + MAPBORDER*2 tile high will not scroll at all vertically
+//
+	originxmax = (mapwidth-MAPBORDER-SCREENTILESWIDE)*TILEGLOBAL;
+	originymax = (mapheight-MAPBORDER-SCREENTILESHIGH)*TILEGLOBAL;
+	if (originxmax<originxmin)		// for very small maps
+		originxmax=originxmin;
+	if (originymax<originymin)
+		originymax=originymin;
+
+//
+// clear out the lists
+//
+	RFL_InitSpriteList ();
+	RFL_InitAnimList ();
+	RFL_ClearScrollBlocks ();
+	RF_SetScrollBlock (0,MAPBORDER-1,true);
+	RF_SetScrollBlock (0,mapheight-MAPBORDER,true);
+	RF_SetScrollBlock (MAPBORDER-1,0,false);
+	RF_SetScrollBlock (mapwidth-MAPBORDER,0,false);
+
+
+	lasttimecount = TimeCount;		// setup for adaptive timing
+	tics = 1;
+}
+
+//===========================================================================
+
+#ifdef KEEN6
+/*
+==========================
+=
+= RFL_CheckTileSound
+=
+= Checks if the tile plays a sound and if so adds that info to the animation
+=
+==========================
+*/
+
+#define NUMSOUNDTILES 2
+typedef struct {
+	unsigned tilenums[NUMSOUNDTILES];
+	int sounds[NUMSOUNDTILES];
+} tilesoundtype;
+
+tilesoundtype far soundtiles = {
+	{2152|0x8000, 2208|0x8000},
+	{SND_STOMP,   SND_FLAME}
+};
+
+void RFL_CheckTileSound(tiletype *anim, unsigned tile)
+{
+	int i;
+
+	for (i=0; i<NUMSOUNDTILES; i++)
+	{
+		if (soundtiles.tilenums[i] == tile)
+		{
+			anim->soundtile = tile;
+			anim->sound = soundtiles.sounds[i];
+			break;
+		}
+	}
+}
+
+#endif
+
+//===========================================================================
+
+/*
+==========================
+=
+= RF_MarkTileGraphics
+=
+= Goes through mapplane[0/1] and marks all background/foreground tiles
+= needed, then follows all animation sequences to make sure animated
+= tiles get all the stages.  Every unique animating tile is given an
+= entry in allanims[], so every instance of that tile will animate at the
+= same rate.  The info plane for each animating tile will hold a pointer
+= into allanims[], therefore you can't have both an animating foreground
+= and background tile in the same spot!
+=
+==========================
+*/
+
+void RF_MarkTileGraphics (void)
+{
+	unsigned	size;
+	int			tile,next,anims,change;
+	unsigned	far	*start,far *end,far *info;
+	unsigned	i,tilehigh;
+	char		str[80],str2[10];
+
+	memset (allanims,0,sizeof(allanims));
+	numanimchains = 0;
+
+	size = mapwidth*mapheight;
+
+//
+// background plane
+//
+	start = mapsegs[0];
+	info = mapsegs[2];
+	end = start+size;
+	do
+	{
+		tile = *start++;
+		if (tile>=0)			// <0 is a tile that is never drawn
+		{
+			CA_MarkGrChunk(STARTTILE16+tile);
+			if (tinf[ANIM+tile])
+			{
+				// this tile will animated
+
+				if (tinf[SPEED+tile])
+				{
+					if (!tinf[ANIM+tile])
+					{
+						strcpy (str,"RF_MarkTileGraphics: Background anim of 0:");
+						itoa (tile,str2,10);
+						strcat (str,str2);
+						Quit (str);
+					}
+					for (i=0;i<numanimchains;i++)
+						if (allanims[i].current == tile)
+						{
+							*info = (unsigned)&allanims[i];
+							goto nextback;
+						}
+
+					// new chain of animating tiles
+
+					if (i>=MAXANIMTYPES)
+						Quit ("RF_MarkTileGraphics: Too many unique animated tiles!");
+					allanims[i].current = tile;
+					allanims[i].count = tinf[SPEED+tile];
+#ifdef KEEN6
+					allanims[i].visible = 0;
+					allanims[i].sound = -1;
+#endif
+					*info = (unsigned)&allanims[i];
+					numanimchains++;
+				}
+#ifdef KEEN6
+				RFL_CheckTileSound(&allanims[i], tile);
+#endif
+
+				anims = 0;
+				change = (signed char)(tinf[ANIM+tile]);
+				next = tile+change;
+				while (change && next != tile)
+				{
+#ifdef KEEN6
+					RFL_CheckTileSound(&allanims[i], next);
+#endif
+					CA_MarkGrChunk(STARTTILE16+next);
+					change = (signed char)(tinf[ANIM+next]);
+					next += change;
+					if (++anims > 20)
+					{
+						strcpy (str,"RF_MarkTileGraphics: Unending background animation:");
+						itoa (next,str2,10);
+						strcat (str,str2);
+						Quit (str);
+					}
+				}
+
+			}
+		}
+nextback:
+		info++;
+	} while (start<end);
+
+//
+// foreground plane
+//
+	start = mapsegs[1];
+	info = mapsegs[2];
+	end = start+size;
+	do
+	{
+		tile = *start++;
+		if (tile>=0)			// <0 is a tile that is never drawn
+		{
+			CA_MarkGrChunk(STARTTILE16M+tile);
+			if (tinf[MANIM+tile])
+			{
+				// this tile will animated
+
+				if (tinf[MSPEED+tile])
+				{
+					if (!tinf[MANIM+tile])
+					{
+						strcpy (str,"RF_MarkTileGraphics: Foreground anim of 0:");
+						itoa (tile,str2,10);
+						strcat (str,str2);
+						Quit (str);
+					}
+					tilehigh = tile | 0x8000;	// foreground tiles have high bit
+					for (i=0;i<numanimchains;i++)
+						if (allanims[i].current == tilehigh)
+						{
+							*info = (unsigned)&allanims[i];
+							goto nextfront;
+						}
+
+					// new chain of animating tiles
+
+					if (i>=MAXANIMTYPES)
+						Quit ("RF_MarkTileGraphics: Too many unique animated tiles!");
+					allanims[i].current = tilehigh;
+					allanims[i].count = tinf[MSPEED+tile];
+#ifdef KEEN6
+					allanims[i].visible = 0;
+					allanims[i].sound = -1;
+#endif
+					*info = (unsigned)&allanims[i];
+					numanimchains++;
+				}
+
+#ifdef KEEN6
+				RFL_CheckTileSound(&allanims[i], tilehigh);
+#endif
+				anims = 0;
+				change = (signed char)(tinf[MANIM+tile]);
+				next = tile+change;
+				while (change && next != tile)
+				{
+#ifdef KEEN6
+					RFL_CheckTileSound(&allanims[i], next | 0x8000);	// foreground tiles have high bit
+#endif
+					CA_MarkGrChunk(STARTTILE16M+next);
+					change = (signed char)(tinf[MANIM+next]);
+					next += change;
+					if (++anims > 20)
+					{
+						strcpy (str,"RF_MarkTileGraphics: Unending foreground animation:");
+						itoa (next,str2,10);
+						strcat (str,str2);
+						Quit (str);
+					}
+				}
+
+			}
+		}
+nextfront:
+		info++;
+	} while (start<end);
+}
+
+
+//===========================================================================
+
+
+/*
+=========================
+=
+= RFL_InitAnimList
+=
+= Call to clear out the entire animating tile list and return all of them to
+= the free list.
+=
+=========================
+*/
+
+void RFL_InitAnimList (void)
+{
+	int	i;
+
+	animfreeptr = &animarray[0];
+
+	for (i=0;i<MAXANIMTILES-1;i++)
+		animarray[i].nexttile = &animarray[i+1];
+
+	animarray[i].nexttile = NULL;
+
+	animhead = NULL;			// nothing in list
+
+#ifdef KEEN6
+	{
+		tiletype *anim;
+
+		for (anim = allanims; anim->current != 0; anim++)
+			anim->visible = 0;
+	}
+#endif
+}
+
+
+/*
+====================
+=
+= RFL_CheckForAnimTile
+=
+====================
+*/
+
+void RFL_CheckForAnimTile (unsigned x, unsigned y)
+{
+	unsigned 	tile,offset,speed,lasttime,thistime,timemissed;
+	unsigned	far *map;
+	animtiletype	*anim,*next;
+
+// the info plane of each animating tile has a near pointer into allanims[]
+// which gives the current state of all concurrently animating tiles
+
+	offset = mapbwidthtable[y]/2+x;
+
+//
+// background
+//
+	map = mapsegs[0]+offset;
+	tile = *map;
+	if (tinf[ANIM+tile] && tinf[SPEED+tile])
+	{
+		if (!animfreeptr)
+			Quit ("RF_CheckForAnimTile: No free spots in tilearray!");
+		anim = animfreeptr;
+		animfreeptr = animfreeptr->nexttile;
+		next = animhead;				// stick it at the start of the list
+		animhead = anim;
+		if (next)
+			next->prevptr = &anim->nexttile;
+		anim->nexttile = next;
+		anim->prevptr = &animhead;
+
+		anim->x = x;
+		anim->y = y;
+		anim->tile = tile;
+		anim->mapplane = map;
+		anim->chain = (tiletype *)*(mapsegs[2]+offset);
+#ifdef KEEN6
+		anim->chain->visible++;
+#endif
+	}
+
+//
+// foreground
+//
+	map = mapsegs[1]+offset;
+	tile = *map;
+	if (tinf[MANIM+tile] && tinf[MSPEED+tile])
+	{
+		if (!animfreeptr)
+			Quit ("RF_CheckForAnimTile: No free spots in tilearray!");
+		anim = animfreeptr;
+		animfreeptr = animfreeptr->nexttile;
+		next = animhead;				// stick it at the start of the list
+		animhead = anim;
+		if (next)
+			next->prevptr = &anim->nexttile;
+		anim->nexttile = next;
+		anim->prevptr = &animhead;
+
+		anim->x = x;
+		anim->y = y;
+		anim->tile = tile;
+		anim->mapplane = map;
+		anim->chain = (tiletype *)*(mapsegs[2]+offset);
+#ifdef KEEN6
+		anim->chain->visible++;
+#endif
+	}
+
+}
+
+
+/*
+====================
+=
+= RFL_RemoveAnimsOnX
+=
+====================
+*/
+
+void RFL_RemoveAnimsOnX (unsigned x)
+{
+	animtiletype *current,*next;
+
+	current = animhead;
+	while (current)
+	{
+		if (current->x == x)
+		{
+#ifdef KEEN6
+			current->chain->visible--;
+#endif
+			*(void **)current->prevptr = current->nexttile;
+			if (current->nexttile)
+				current->nexttile->prevptr = current->prevptr;
+			next = current->nexttile;
+			current->nexttile = animfreeptr;
+			animfreeptr = current;
+			current = next;
+		}
+		else
+			current = current->nexttile;
+	}
+}
+
+
+/*
+====================
+=
+= RFL_RemoveAnimsOnY
+=
+====================
+*/
+
+void RFL_RemoveAnimsOnY (unsigned y)
+{
+	animtiletype *current,*next;
+
+	current = animhead;
+	while (current)
+	{
+		if (current->y == y)
+		{
+#ifdef KEEN6
+			current->chain->visible--;
+#endif
+			*(void **)current->prevptr = current->nexttile;
+			if (current->nexttile)
+				current->nexttile->prevptr = current->prevptr;
+			next = current->nexttile;
+			current->nexttile = animfreeptr;
+			animfreeptr = current;
+			current = next;
+		}
+		else
+			current = current->nexttile;
+	}
+}
+
+
+/*
+====================
+=
+= RFL_RemoveAnimsInBlock
+=
+====================
+*/
+
+void RFL_RemoveAnimsInBlock (unsigned x, unsigned y, unsigned width, unsigned height)
+{
+	animtiletype *current,*next;
+
+	current = animhead;
+	while (current)
+	{
+		if (current->x - x < width && current->y - y < height)
+		{
+#ifdef KEEN6
+			current->chain->visible--;
+#endif
+			*(void **)current->prevptr = current->nexttile;
+			if (current->nexttile)
+				current->nexttile->prevptr = current->prevptr;
+			next = current->nexttile;
+			current->nexttile = animfreeptr;
+			animfreeptr = current;
+			current = next;
+		}
+		else
+			current = current->nexttile;
+	}
+}
+
+
+/*
+====================
+=
+= RFL_AnimateTiles
+=
+====================
+*/
+
+void RFL_AnimateTiles (void)
+{
+	animtiletype *current;
+	unsigned	updateofs,tile,x,y;
+	tiletype	*anim;
+
+//
+// animate the lists of tiles
+//
+	anim = &allanims[0];
+	while (anim->current)
+	{
+		anim->count-=tics;
+		while ( anim->count < 1)
+		{
+			if (anim->current & 0x8000)
+			{
+				tile = anim->current & 0x7fff;
+				tile += (signed char)tinf[MANIM+tile];
+				anim->count += tinf[MSPEED+tile];
+				tile |= 0x8000;
+			}
+			else
+			{
+				tile = anim->current;
+				tile += (signed char)tinf[ANIM+tile];
+				anim->count += tinf[SPEED+tile];
+			}
+			anim->current = tile;
+#ifdef KEEN6
+			if (anim->visible && anim->current == anim->soundtile && anim->sound != -1)
+			{
+				SD_PlaySound(anim->sound);
+			}
+#endif
+		}
+		anim++;
+	}
+
+
+//
+// traverse the list of animating tiles
+//
+	current = animhead;
+	while (current)
+	{
+		tile =current->chain->current;
+		if ( tile != current->tile)
+		{
+		// tile has animated
+		//
+		// remove tile from master screen cache,
+		// change a tile to its next state, set the structure up for
+		// next animation, and post an update region to both update pages
+		//
+			current->tile = tile;
+
+			*(current->mapplane) = tile & 0x7fff; 		// change in map
+
+			x = current->x-originxtile;
+			y = current->y-originytile;
+
+			if (x>=PORTTILESWIDE || y>=PORTTILESHIGH)
+				Quit ("RFL_AnimateTiles: Out of bounds!");
+
+			updateofs = uwidthtable[y] + x;
+			RFL_NewTile(updateofs);				// puts "1"s in both pages
+		}
+		current = current->nexttile;
+	}
+}
+
+
+//===========================================================================
+
+/*
+=========================
+=
+= RFL_InitSpriteList
+=
+= Call to clear out the entire sprite list and return all of them to
+= the free list.
+=
+=========================
+*/
+
+void RFL_InitSpriteList (void)
+{
+	int	i;
+
+	spritefreeptr = &spritearray[0];
+	for (i=0;i<MAXSPRITES-1;i++)
+		spritearray[i].nextsprite = &spritearray[i+1];
+
+	spritearray[i].nextsprite = NULL;
+
+// NULL in all priority levels
+
+	memset (prioritystart,0,sizeof(prioritystart));
+}
+
+//===========================================================================
+
+/*
+=================
+=
+= RFL_CalcOriginStuff
+=
+= Calculate all the global variables for a new position
+= Long parms so position can be clipped to a maximum near 64k
+=
+=================
+*/
+
+void RFL_CalcOriginStuff (long x, long y)
+{
+	originxglobal = x;
+	originyglobal = y;
+	originxtile = originxglobal>>G_T_SHIFT;
+	originytile = originyglobal>>G_T_SHIFT;
+	originxscreen = originxtile<<SX_T_SHIFT;
+	originyscreen = originytile<<SY_T_SHIFT;
+	originmap = mapbwidthtable[originytile] + originxtile*2;
+
+#if GRMODE == EGAGR
+	panx = (originxglobal>>G_P_SHIFT) & 15;
+	pansx = panx & 8;
+	pany = pansy = (originyglobal>>G_P_SHIFT) & 15;
+	panadjust = panx/8 + ylookup[pany];
+#endif
+
+#if GRMODE == CGAGR
+	panx = (originxglobal>>G_P_SHIFT) & 15;
+	pansx = panx & 12;
+	pany = pansy = (originyglobal>>G_P_SHIFT) & 15;
+	panadjust = pansx/4 + ylookup[pansy];
+#endif
+
+}
+
+
+/*
+=================
+=
+= RFL_ClearScrollBlocks
+=
+=================
+*/
+
+void RFL_ClearScrollBlocks (void)
+{
+	hscrollblocks = vscrollblocks = 0;
+}
+
+
+/*
+=================
+=
+= RF_SetScrollBlock
+=
+= Sets a horizontal or vertical scroll block
+= a horizontal block is ----, meaning it blocks up/down movement
+=
+=================
+*/
+
+void RF_SetScrollBlock (int x, int y, boolean horizontal)
+{
+	if (horizontal)
+	{
+		hscrolledge[hscrollblocks] = y;
+		if (hscrollblocks++ == MAXSCROLLEDGES)
+			Quit ("RF_SetScrollBlock: Too many horizontal scroll blocks");
+	}
+	else
+	{
+		vscrolledge[vscrollblocks] = x;
+		if (vscrollblocks++ == MAXSCROLLEDGES)
+			Quit ("RF_SetScrollBlock: Too many vertical scroll blocks");
+	}
+}
+
+
+/*
+=================
+=
+= RFL_BoundScroll
+=
+= Bound a given x/y movement to scroll blocks
+=
+=================
+*/
+
+void RFL_BoundScroll (int x, int y)
+{
+	int	check,newxtile,newytile;
+
+	originxglobal += x;
+	originyglobal += y;
+
+	newxtile= originxglobal >> G_T_SHIFT;
+	newytile = originyglobal >> G_T_SHIFT;
+
+	if (x>0)
+	{
+		newxtile+=SCREENTILESWIDE;
+		for (check=0;check<vscrollblocks;check++)
+			if (vscrolledge[check] == newxtile)
+			{
+				originxglobal = originxglobal&0xff00;
+				break;
+			}
+	}
+	else if (x<0)
+	{
+		for (check=0;check<vscrollblocks;check++)
+			if (vscrolledge[check] == newxtile)
+			{
+				originxglobal = (originxglobal&0xff00)+0x100;
+				break;
+			}
+	}
+
+
+	if (y>0)
+	{
+		newytile+=SCREENTILESHIGH;
+		for (check=0;check<hscrollblocks;check++)
+			if (hscrolledge[check] == newytile)
+			{
+				originyglobal = originyglobal&0xff00;
+				break;
+			}
+	}
+	else if (y<0)
+	{
+		for (check=0;check<hscrollblocks;check++)
+			if (hscrolledge[check] == newytile)
+			{
+				originyglobal = (originyglobal&0xff00)+0x100;
+				break;
+			}
+	}
+
+
+	RFL_CalcOriginStuff (originxglobal, originyglobal);
+}
+
+
+//===========================================================================
+
+/*
+=====================
+=
+= RF_SetRefreshHook
+=
+=====================
+*/
+
+void RF_SetRefreshHook (void (*func) (void) )
+{
+	refreshvector = func;
+}
+
+
+//===========================================================================
+
+/*
+=================
+=
+= RFL_NewRow
+=
+= Bring a new row of tiles onto the port, spawning animating tiles
+=
+=================
+*/
+
+void	RFL_NewRow (int dir)
+{
+	unsigned count,updatespot,updatestep;
+	int		x,y,xstep,ystep;
+
+	switch (dir)
+	{
+	case 0:		// top row
+		updatespot = 0;
+		updatestep = 1;
+		x = originxtile;
+		y = originytile;
+		xstep = 1;
+		ystep = 0;
+		count = PORTTILESWIDE;
+		break;
+
+	case 1:		// right row
+		updatespot = PORTTILESWIDE-1;
+		updatestep = UPDATEWIDE;
+		x = originxtile + PORTTILESWIDE-1;
+		y = originytile;
+		xstep = 0;
+		ystep = 1;
+		count = PORTTILESHIGH;
+		break;
+
+	case 2:		// bottom row
+		updatespot = UPDATEWIDE*(PORTTILESHIGH-1);
+		updatestep = 1;
+		x = originxtile;
+		y = originytile + PORTTILESHIGH-1;
+		xstep = 1;
+		ystep = 0;
+		count = PORTTILESWIDE;
+		break;
+
+	case 3:		// left row
+		updatespot = 0;
+		updatestep = UPDATEWIDE;
+		x = originxtile;
+		y = originytile;
+		xstep = 0;
+		ystep = 1;
+		count = PORTTILESHIGH;
+		break;
+	default:
+		Quit ("RFL_NewRow: Bad dir!");
+	}
+
+	while (count--)
+	{
+		RFL_NewTile(updatespot);
+		RFL_CheckForAnimTile (x,y);
+		updatespot+=updatestep;
+		x+=xstep;
+		y+=ystep;
+	}
+}
+
+//===========================================================================
+
+/*
+=====================
+=
+= RF_ForceRefresh
+=
+=====================
+*/
+
+void RF_ForceRefresh (void)
+{
+	RF_NewPosition (originxglobal,originyglobal);
+	RF_Refresh ();
+	RF_Refresh ();
+}
+
+//===========================================================================
+
+/*
+=====================
+=
+= RF_MapToMap
+=
+= Copies a block of tiles (all three planes) from one point
+= in the map to another, accounting for animating tiles
+=
+=====================
+*/
+
+void RF_MapToMap (unsigned srcx, unsigned srcy,
+				  unsigned destx, unsigned desty,
+				  unsigned width, unsigned height)
+{
+	int			x,y;
+	unsigned	source,destofs,xspot,yspot;
+	unsigned	linedelta,p0,p1,p2,updatespot;
+	unsigned	far *source0, far *source1, far *source2;
+	unsigned	far *dest0, far *dest1, far *dest2;
+	boolean		changed;
+
+	RFL_RemoveAnimsInBlock (destx,desty,width,height);
+
+	source = mapbwidthtable[srcy]/2 + srcx;
+
+	source0 = mapsegs[0]+source;
+	source1 = mapsegs[1]+source;
+	source2 = mapsegs[2]+source;
+
+	destofs = mapbwidthtable[desty]/2 + destx;
+	destofs -= source;
+
+	linedelta = mapwidth - width;
+
+	for (y=0;y<height;y++,source0+=linedelta,source1+=linedelta,source2+=linedelta)
+		for (x=0;x<width;x++,source0++,source1++,source2++)
+		{
+			p0 = *source0;
+			p1 = *source1;
+			p2 = *source2;
+
+			dest0 = source0 + destofs;
+			dest1 = source1 + destofs;
+			dest2 = source2 + destofs;
+
+//
+// only make a new tile if it is different
+//
+			if (p0 != *dest0 || p1 != *dest1 || p2 != *dest2)
+			{
+				*dest0 = p0;
+				*dest1 = p1;
+				*dest2 = p2;
+				changed = true;
+			}
+			else
+				changed = false;
+
+//
+// if tile is on the view port
+//
+			xspot = destx+x-originxtile;
+			yspot = desty+y-originytile;
+			if (yspot < PORTTILESHIGH && xspot < PORTTILESWIDE)
+			{
+				if (changed)
+				{
+					updatespot = uwidthtable[yspot]+xspot;
+					RFL_NewTile(updatespot);
+				}
+				RFL_CheckForAnimTile (destx+x,desty+y);
+			}
+		}
+}
+
+//===========================================================================
+
+
+/*
+=====================
+=
+= RF_MemToMap
+=
+= Copies a string of tiles from main memory to the map,
+= accounting for animating tiles
+=
+=====================
+*/
+
+void RF_MemToMap (unsigned far *source, unsigned plane,
+				  unsigned destx, unsigned desty,
+				  unsigned width, unsigned height)
+{
+	int			x,y;
+	unsigned	xspot,yspot;
+	unsigned	linedelta,updatespot;
+	unsigned	far *dest,old,new;
+	boolean		changed;
+
+	RFL_RemoveAnimsInBlock (destx,desty,width,height);
+
+	dest = mapsegs[plane] + mapbwidthtable[desty]/2 + destx;
+
+	linedelta = mapwidth - width;
+
+	for (y=0;y<height;y++,dest+=linedelta)
+		for (x=0;x<width;x++)
+		{
+			old = *dest;
+			new = *source++;
+			if (old != new)
+			{
+				*dest = new;
+				changed = true;
+			}
+			else
+				changed = false;
+
+			dest++;
+			xspot = destx+x-originxtile;
+			yspot = desty+y-originytile;
+			if (yspot < PORTTILESHIGH && xspot < PORTTILESWIDE)
+			{
+				if (changed)
+				{
+					updatespot = uwidthtable[yspot]+xspot;
+					RFL_NewTile(updatespot);
+				}
+				RFL_CheckForAnimTile (destx+x,desty+y);
+			}
+		}
+}
+
+//===========================================================================
+
+
+/*
+=====================
+=
+= RFL_BoundNewOrigin
+=
+= Copies a string of tiles from main memory to the map,
+= accounting for animating tiles
+=
+=====================
+*/
+
+void RFL_BoundNewOrigin (unsigned orgx,unsigned orgy)
+{
+	int	check,edge;
+
+//
+// calculate new origin related globals
+//
+	if (orgx<originxmin)
+	  orgx=originxmin;
+	else if (orgx>originxmax)
+	  orgx=originxmax;
+
+	if (orgy<originymin)
+	  orgy=originymin;
+	else if (orgy>originymax)
+	  orgy=originymax;
+
+	originxtile = orgx>>G_T_SHIFT;
+	originytile = orgy>>G_T_SHIFT;
+
+	for (check=0;check<vscrollblocks;check++)
+	{
+		edge = vscrolledge[check];
+		if (edge>=originxtile && edge <=originxtile+10)
+		{
+			orgx = (edge+1)*TILEGLOBAL;
+			break;
+		}
+		if (edge>=originxtile+11 && edge <=originxtile+20)
+		{
+			orgx = (edge-20)*TILEGLOBAL;
+			break;
+		}
+	}
+
+	for (check=0;check<hscrollblocks;check++)
+	{
+		edge = hscrolledge[check];
+		if (edge>=originytile && edge <=originytile+6)
+		{
+			orgy = (edge+1)*TILEGLOBAL;
+			break;
+		}
+		if (edge>=originytile+7 && edge <=originytile+13)
+		{
+			orgy = (edge-13)*TILEGLOBAL;
+			break;
+		}
+	}
+
+
+	RFL_CalcOriginStuff (orgx,orgy);
+}
+
+
+//===========================================================================
+
+/*
+=====================
+=
+= RF_ClearBlock
+=
+= Posts erase blocks to clear a certain area of the screen to the master
+= screen, to erase text or something draw directly to the screen
+=
+= Parameters in pixels, but erasure is byte bounded
+=
+=====================
+*/
+
+void RF_ClearBlock (int	x, int y, int width, int height)
+{
+	eraseblocktype block;
+
+#if GRMODE == EGAGR
+	block.screenx = x/8+originxscreen;
+	block.screeny = y+originyscreen;
+	block.width = (width+(x&7)+7)/8;
+	block.height = height;
+	memcpy (eraselistptr[0]++,&block,sizeof(block));
+	memcpy (eraselistptr[1]++,&block,sizeof(block));
+#endif
+
+#if GRMODE == CGAGR
+	block.screenx = x/4+originxscreen;
+	block.screeny = y+originyscreen;
+	block.width = (width+(x&3)+3)/4;
+	block.height = height;
+	memcpy (eraselistptr[0]++,&block,sizeof(block));
+#endif
+
+}
+
+//===========================================================================
+
+/*
+=====================
+=
+= RF_RedrawBlock
+=
+= Causes a number of tiles to be redrawn to the master screen and updated
+=
+= Parameters in pixels, but erasure is tile bounded
+=
+=====================
+*/
+
+void RF_RedrawBlock (int x, int y, int width, int height)
+{
+	int	xx,yy,xl,xh,yl,yh;
+
+	xl=(x+panx)/16;
+	xh=(x+panx+width+15)/16;
+	yl=(y+pany)/16;
+	yh=(y+pany+height+15)/16;
+	for (yy=yl;yy<=yh;yy++)
+		for (xx=xl;xx<=xh;xx++)
+			RFL_NewTile (yy*UPDATEWIDE+xx);
+}
+
+
+//===========================================================================
+
+/*
+=====================
+=
+= RF_CalcTics
+=
+=====================
+*/
+
+void RF_CalcTics (void)
+{
+	long	newtime,oldtimecount;
+
+//
+// calculate tics since last refresh for adaptive timing
+//
+	if (lasttimecount > TimeCount)
+		TimeCount = lasttimecount;		// if the game was paused a LONG time
+
+	if (DemoMode)					// demo recording and playback needs
+	{								// to be constant
+//
+// take DEMOTICS or more tics, and modify Timecount to reflect time taken
+//
+		oldtimecount = lasttimecount;
+		while (TimeCount<oldtimecount+DEMOTICS*2)
+		;
+		lasttimecount = oldtimecount + DEMOTICS;
+		TimeCount = lasttimecount + DEMOTICS;
+		tics = DEMOTICS;
+	}
+	else
+	{
+//
+// non demo, so report actual time
+//
+		do
+		{
+			newtime = TimeCount;
+			tics = newtime-lasttimecount;
+		} while (tics<MINTICS);
+		lasttimecount = newtime;
+
+#ifdef PROFILE
+			strcpy (scratch,"\tTics:");
+			itoa (tics,str,10);
+			strcat (scratch,str);
+			strcat (scratch,"\n");
+			write (profilehandle,scratch,strlen(scratch));
+#endif
+
+		if (tics>MAXTICS)
+		{
+			TimeCount -= (tics-MAXTICS);
+			tics = MAXTICS;
+		}
+	}
+}
+
+//===========================================================================
+
+/*
+=====================
+=
+= RF_FindFreeBuffer
+=
+= Finds the start of unused, non visable buffer space
+=
+=====================
+*/
+
+unsigned RF_FindFreeBuffer (void)
+{
+	unsigned	spot,i,j;
+	boolean		ok;
+
+	for (i=0;i<3;i++)
+	{
+		spot = screenstart[i]+SCREENSPACE;
+		ok = true;
+		for (j=0;j<3;j++)
+			if (spot == screenstart[j])
+			{
+				ok = false;
+				break;
+			}
+		if (ok)
+			return spot;
+	}
+
+	return 0;	// never get here...
+}
+
+/*
+=============================================================================
+
+					EGA specific routines
+
+=============================================================================
+*/
+
+#if GRMODE == EGAGR
+
+/*
+=====================
+=
+= RF_NewPosition EGA
+=
+=====================
+*/
+
+void RF_NewPosition (unsigned x, unsigned y)
+{
+	int mx,my;
+	byte	*page0ptr,*page1ptr;
+	unsigned 	updatenum;
+
+	RFL_BoundNewOrigin (x,y);
+//
+// clear out all animating tiles
+//
+	RFL_InitAnimList ();
+
+//
+// set up the new update arrays at base position
+//
+	updatestart[0] = baseupdatestart[0];
+	updatestart[1] = baseupdatestart[1];
+	updateptr = updatestart[otherpage];
+
+	page0ptr = updatestart[0]+PORTTILESWIDE;	// used to stick "0"s after rows
+	page1ptr = updatestart[1]+PORTTILESWIDE;
+
+	updatenum = 0;				// start at first visable tile
+
+	for (my=0;my<PORTTILESHIGH;my++)
+	{
+		for (mx=0;mx<PORTTILESWIDE;mx++)
+		{
+			RFL_NewTile(updatenum);			// puts "1"s in both pages
+			RFL_CheckForAnimTile(mx+originxtile,my+originytile);
+			updatenum++;
+		}
+		updatenum++;
+		*page0ptr = *page1ptr = 0; // set a 0 at end of a line of tiles
+		page0ptr+=(PORTTILESWIDE+1);
+		page1ptr+=(PORTTILESWIDE+1);
+	}
+	*(word *)(page0ptr-PORTTILESWIDE)
+		= *(word *)(page1ptr-PORTTILESWIDE) = UPDATETERMINATE;
+}
+
+//===========================================================================
+
+
+/*
+=====================
+=
+= RF_Scroll  EGA
+=
+= Move the origin x/y global coordinates, readjust the screen panning, and
+= scroll if needed.  If the scroll distance is greater than one tile, the
+= entire screen will be redrawn (this could be generalized, but scrolling
+= more than one tile per refresh is a bad idea!).
+=
+=====================
+*/
+
+void RF_Scroll (int x, int y)
+{
+	long		neworgx,neworgy;
+	int			i,deltax,deltay,absdx,absdy;
+	int			oldxt,oldyt,move,yy;
+	unsigned	updatespot;
+	byte		*update0,*update1;
+	unsigned	oldpanx,oldpanadjust,oldscreen,newscreen,screencopy;
+	int			screenmove;
+
+	oldxt = originxtile;
+	oldyt = originytile;
+	oldpanadjust = panadjust;
+	oldpanx = panx;
+
+	RFL_BoundScroll (x,y);
+
+	deltax = originxtile - oldxt;
+	absdx = abs(deltax);
+	deltay = originytile - oldyt;
+	absdy = abs(deltay);
+
+	if (absdx>1 || absdy>1)
+	{
+	//
+	// scrolled more than one tile, so start from scratch
+	//
+		RF_NewPosition(originxglobal,originyglobal);
+		return;
+	}
+
+	if (!absdx && !absdy)
+		return;					// the screen has not scrolled an entire tile
+
+
+//
+// adjust screens and handle SVGA crippled compatability mode
+//
+	screenmove = deltay*16*SCREENWIDTH + deltax*TILEWIDTH;
+	for (i=0;i<3;i++)
+	{
+		screenstart[i]+= screenmove;
+		if (compatability && screenstart[i] > (0x10000l-SCREENSPACE) )
+		{
+			//
+			// move the screen to the opposite end of the buffer
+			//
+			screencopy = screenmove>0 ? FREEEGAMEM : -FREEEGAMEM;
+			oldscreen = screenstart[i] - screenmove;
+			newscreen = oldscreen + screencopy;
+			screenstart[i] = newscreen + screenmove;
+			VW_ScreenToScreen (oldscreen,newscreen,
+				PORTTILESWIDE*2,PORTTILESHIGH*16);
+
+			if (i==screenpage)
+				VW_SetScreen(newscreen+oldpanadjust,oldpanx & xpanmask);
+		}
+	}
+	bufferofs = screenstart[otherpage];
+	displayofs = screenstart[screenpage];
+	masterofs = screenstart[2];
+
+
+//
+// float the update regions
+//
+	move = deltax;
+	if (deltay==1)
+	  move += UPDATEWIDE;
+	else if (deltay==-1)
+	  move -= UPDATEWIDE;
+
+	updatestart[0]+=move;
+	updatestart[1]+=move;
+
+//
+// draw the new tiles just scrolled on to the master screen, and
+// mark them as needing to be copied to each screen next refreshes
+// Make sure a zero is at the end of each row in update
+//
+
+	if (deltax)
+	{
+		if (deltax==1)
+		{
+			RFL_NewRow (1);			// new right row
+			RFL_RemoveAnimsOnX (originxtile-1);
+		}
+		else
+		{
+			RFL_NewRow (3);			// new left row
+			RFL_RemoveAnimsOnX (originxtile+PORTTILESWIDE);
+		}
+
+		update0 = updatestart[0]+PORTTILESWIDE;
+		update1 = updatestart[1]+PORTTILESWIDE;
+		for	(yy=0;yy<PORTTILESHIGH;yy++)
+		{
+			*update0 = *update1 = 0;	// drop a 0 at end of each row
+			update0+=UPDATEWIDE;
+			update1+=UPDATEWIDE;
+		}
+	}
+
+//----------------
+
+	if (deltay)
+	{
+		if (deltay==1)
+		{
+			updatespot = UPDATEWIDE*(PORTTILESHIGH-1);
+			RFL_NewRow (2);			// new bottom row
+			RFL_RemoveAnimsOnY (originytile-1);
+		}
+		else
+		{
+			updatespot = 0;
+			RFL_NewRow (0);			// new top row
+			RFL_RemoveAnimsOnY (originytile+PORTTILESHIGH);
+		}
+
+		*(updatestart[0]+updatespot+PORTTILESWIDE) =
+			*(updatestart[1]+updatespot+PORTTILESWIDE) = 0;
+	}
+
+//----------------
+
+	//
+	// place a new terminator
+	//
+	update0 = updatestart[0]+UPDATEWIDE*PORTTILESHIGH-1;
+	update1 = updatestart[1]+UPDATEWIDE*PORTTILESHIGH-1;
+	*update0++ = *update1++ = 0;
+	*(unsigned *)update0 = *(unsigned *)update1 = UPDATETERMINATE;
+}
+
+//===========================================================================
+
+/*
+=====================
+=
+= RF_PlaceSprite   EGA
+=
+=====================
+*/
+
+void RF_PlaceSprite (void **user,unsigned globalx,unsigned globaly,
+	unsigned spritenumber, drawtype draw, int priority)
+{
+	spritelisttype	register *sprite,*next;
+	spritetabletype far *spr;
+	spritetype _seg	*block;
+	unsigned	shift,pixx;
+	char		str[80],str2[10];
+
+	if (!spritenumber || spritenumber == (unsigned)-1)
+	{
+		RF_RemoveSprite (user);
+		return;
+	}
+
+	sprite = (spritelisttype *)*user;
+
+	if	(sprite)
+	{
+	// sprite allready exists in the list, so we can use it's block
+
+	//
+	// post an erase block to both pages by copying screenx,screeny,width,height
+	// both pages may not need to be erased if the sprite just changed last frame
+	//
+		if (sprite->updatecount<2)
+		{
+			if (!sprite->updatecount)
+				memcpy (eraselistptr[otherpage]++,sprite,sizeof(eraseblocktype));
+			memcpy (eraselistptr[screenpage]++,sprite,sizeof(eraseblocktype));
+		}
+
+		if (priority != sprite->priority)
+		{
+		// sprite mvoed to another priority, so unlink the old one and
+		// relink it in the new priority
+
+			next = sprite->nextsprite;			// cut old links
+			if (next)
+				next->prevptr = sprite->prevptr;
+			*sprite->prevptr = next;
+			goto linknewspot;
+		}
+	}
+	else
+	{
+	// this is a brand new sprite, so allocate a block from the array
+
+		if (!spritefreeptr)
+			Quit ("RF_PlaceSprite: No free spots in spritearray!");
+
+		sprite = spritefreeptr;
+		spritefreeptr = spritefreeptr->nextsprite;
+
+linknewspot:
+		next = prioritystart[priority];		// stick it in new spot
+		if (next)
+			next->prevptr = &sprite->nextsprite;
+		sprite->nextsprite = next;
+		prioritystart[priority] = sprite;
+		sprite->prevptr = &prioritystart[priority];
+	}
+
+//
+// write the new info to the sprite
+//
+	spr = &spritetable[spritenumber-STARTSPRITES];
+	block = (spritetype _seg *)grsegs[spritenumber];
+
+	if (!block)
+	{
+		strcpy (str,"RF_PlaceSprite: Placed an uncached sprite:");
+		itoa (spritenumber,str2,10);
+		strcat (str,str2);
+		Quit (str);
+	}
+
+	globaly+=spr->orgy;
+	globalx+=spr->orgx;
+
+	pixx = globalx >> G_SY_SHIFT;
+	if (nopan)
+		shift = 0;
+	else
+		shift = (pixx&7)/2;
+
+	sprite->screenx = pixx >> (G_EGASX_SHIFT-G_SY_SHIFT);
+	sprite->screeny = globaly >> G_SY_SHIFT;
+	sprite->width = block->width[shift];
+	sprite->height = spr->height;
+	sprite->grseg = spritenumber;
+	sprite->sourceofs = block->sourceoffset[shift];
+	sprite->planesize = block->planesize[shift];
+	sprite->draw = draw;
+	sprite->priority = priority;
+	sprite->tilex = sprite->screenx >> SX_T_SHIFT;
+	sprite->tiley = sprite->screeny >> SY_T_SHIFT;
+	sprite->tilewide = ( (sprite->screenx + sprite->width -1) >> SX_T_SHIFT )
+		- sprite->tilex + 1;
+	sprite->tilehigh = ( (sprite->screeny + sprite->height -1) >> SY_T_SHIFT )
+		- sprite->tiley + 1;
+
+	sprite->updatecount = 2;		// draw on next two refreshes
+
+// save the sprite pointer off in the user's pointer so it can be moved
+// again later
+
+	*user = sprite;
+}
+
+//===========================================================================
+
+/*
+=====================
+=
+= RF_RemoveSprite  EGA
+=
+=====================
+*/
+
+void RF_RemoveSprite (void **user)
+{
+	spritelisttype	*sprite,*next;
+
+	sprite = (spritelisttype *)*user;
+	if (!sprite)
+		return;
+
+//
+// post an erase block to both pages by copying screenx,screeny,width,height
+// both pages may not need to be erased if the sprite just changed last frame
+//
+	if (sprite->updatecount<2)
+	{
+		if (!sprite->updatecount)
+			memcpy (eraselistptr[otherpage]++,sprite,sizeof(eraseblocktype));
+		memcpy (eraselistptr[screenpage]++,sprite,sizeof(eraseblocktype));
+	}
+
+//
+// unlink the sprite node
+//
+	next = sprite->nextsprite;
+	if (next)						// if (!next), sprite is last in chain
+		next->prevptr = sprite->prevptr;
+	*sprite->prevptr = next;
+
+//
+// add it back to the free list
+//
+	sprite->nextsprite = spritefreeptr;
+	spritefreeptr = sprite;
+
+//
+// null the users pointer, so next time that actor gets placed, it will
+// allocate a new block
+//
+
+	*user = 0;
+}
+
+
+//===========================================================================
+
+
+/*
+====================
+=
+= RFL_EraseBlocks  EGA
+=
+= Write mode 1 should be set
+=
+====================
+*/
+
+void RFL_EraseBlocks (void)
+{
+	eraseblocktype	*block,*done;
+	int			screenxh,screenyh;
+	unsigned	pos,xtl,ytl,xth,yth,x,y;
+	byte		*updatespot;
+	unsigned	updatedelta;
+	unsigned	erasecount;
+
+#ifdef PROFILE
+	erasecount = 0;
+#endif
+
+	block = otherpage ? &eraselist[1][0] : &eraselist[0][0];
+
+	done = eraselistptr[otherpage];
+
+	while (block != done)
+	{
+
+	//
+	// clip the block to the current screen view
+	//
+		block->screenx -= originxscreen;
+		block->screeny -= originyscreen;
+
+		if (block->screenx < 0)
+		{
+			block->width += block->screenx;
+			if (block->width<1)
+				goto next;
+			block->screenx = 0;
+		}
+
+		if (block->screeny < 0)
+		{
+			block->height += block->screeny;
+			if (block->height<1)
+				goto next;
+			block->screeny = 0;
+		}
+
+		screenxh = block->screenx + block->width;
+		screenyh = block->screeny + block->height;
+
+		if (screenxh > EGAPORTSCREENWIDE)
+		{
+			block->width = EGAPORTSCREENWIDE-block->screenx;
+			screenxh = block->screenx + block->width;
+		}
+
+		if (screenyh > PORTSCREENHIGH)
+		{
+			block->height = PORTSCREENHIGH-block->screeny;
+			screenyh = block->screeny + block->height;
+		}
+
+		if (block->width<1 || block->height<1)
+			goto next;
+
+	//
+	// erase the block by copying from the master screen
+	//
+		pos = ylookup[block->screeny]+block->screenx;
+		VW_ScreenToScreen (masterofs+pos,bufferofs+pos,
+			block->width,block->height);
+
+	//
+	// put 2s in update where the block was, to force sprites to update
+	//
+		xtl = block->screenx >> SX_T_SHIFT;
+		xth = (block->screenx+block->width-1) >> SX_T_SHIFT;
+		ytl = block->screeny >> SY_T_SHIFT;
+		yth = (block->screeny+block->height-1) >> SY_T_SHIFT;
+
+		updatespot = updateptr + uwidthtable[ytl] + xtl;
+		updatedelta = UPDATEWIDE - (xth-xtl+1);
+
+		for (y=ytl;y<=yth;y++)
+		{
+			for (x=xtl;x<=xth;x++)
+				*updatespot++ = 2;
+			updatespot += updatedelta;		// down to next line
+		}
+#ifdef PROFILE
+		erasecount++;
+#endif
+
+next:
+		block++;
+	}
+	eraselistptr[otherpage] = otherpage ? &eraselist[1][0] : &eraselist[0][0];
+#ifdef PROFILE
+	strcpy (scratch,"\tErase:");
+	itoa (erasecount,str,10);
+	strcat (scratch,str);
+	write (profilehandle,scratch,strlen(scratch));
+#endif
+
+}
+
+
+/*
+====================
+=
+= RFL_UpdateSprites EGA
+=
+= NOTE: Implement vertical clipping!
+=
+====================
+*/
+
+void RFL_UpdateSprites (void)
+{
+	spritelisttype	*sprite;
+	int	portx,porty,x,y,xtl,xth,ytl,yth;
+	int	priority;
+	unsigned dest;
+	byte		*updatespot,*baseupdatespot;
+	unsigned	updatedelta;
+	unsigned	updatecount;
+	unsigned	height,sourceofs;
+
+#ifdef PROFILE
+	updatecount = 0;
+#endif
+
+	for (priority=0;priority<PRIORITIES;priority++)
+	{
+		if (priority==MASKEDTILEPRIORITY)
+			RFL_MaskForegroundTiles ();
+
+		for (sprite = prioritystart[priority]; sprite ;
+			sprite = (spritelisttype *)sprite->nextsprite)
+		{
+		//
+		// see if the sprite has any visable area in the port
+		//
+
+			portx = sprite->screenx - originxscreen;
+			porty = sprite->screeny - originyscreen;
+			xtl = portx >> SX_T_SHIFT;
+			xth = (portx + sprite->width-1) >> SX_T_SHIFT;
+			ytl = porty >> SY_T_SHIFT;
+			yth = (porty + sprite->height-1) >> SY_T_SHIFT;
+
+			if (xtl<0)
+			  xtl = 0;
+			if (xth>=PORTTILESWIDE)
+			  xth = PORTTILESWIDE-1;
+			if (ytl<0)
+			  ytl = 0;
+			if (yth>=PORTTILESHIGH)
+			  yth = PORTTILESHIGH-1;
+
+			if (xtl>xth || ytl>yth)
+				continue;
+
+		//
+		// see if it's visable area covers any non 0 update tiles
+		//
+			updatespot = baseupdatespot = updateptr + uwidthtable[ytl] + xtl;
+			updatedelta = UPDATEWIDE - (xth-xtl+1);
+
+			if (sprite->updatecount)
+			{
+				sprite->updatecount--;			// the sprite was just placed,
+				goto redraw;					// so draw it for sure
+			}
+
+			for (y=ytl;y<=yth;y++)
+			{
+				for (x=xtl;x<=xth;x++)
+					if (*updatespot++)
+						goto redraw;
+				updatespot += updatedelta;		// down to next line
+			}
+			continue;							// no need to update
+
+redraw:
+		//
+		// set the tiles it covers to 3, because those tiles are being
+		// updated
+		//
+			updatespot = baseupdatespot;
+			for (y=ytl;y<=yth;y++)
+			{
+				for (x=xtl;x<=xth;x++)
+					*updatespot++ = 3;
+				updatespot += updatedelta;		// down to next line
+			}
+		//
+		// draw it!
+		//
+			height = sprite->height;
+			sourceofs = sprite->sourceofs;
+			if (porty<0)
+			{
+				height += porty;					// clip top off
+				sourceofs -= porty*sprite->width;
+				porty = 0;
+			}
+			else if (porty+height>PORTSCREENHIGH)
+			{
+				height = PORTSCREENHIGH - porty;    // clip bottom off
+			}
+
+			dest = bufferofs + ylookup[porty] + portx;
+
+			switch (sprite->draw)
+			{
+			case spritedraw:
+				VW_MaskBlock(grsegs[sprite->grseg], sourceofs,
+					dest,sprite->width,height,sprite->planesize);
+				break;
+
+			case maskdraw:
+				VW_InverseMask(grsegs[sprite->grseg], sourceofs,
+					dest,sprite->width,height);
+				break;
+
+			}
+#ifdef PROFILE
+			updatecount++;
+#endif
+
+
+		}
+	}
+#ifdef PROFILE
+	strcpy (scratch,"\tSprites:");
+	itoa (updatecount,str,10);
+	strcat (scratch,str);
+	write (profilehandle,scratch,strlen(scratch));
+#endif
+
+}
+
+
+/*
+=====================
+=
+= RF_Refresh   EGA
+=
+= All routines will draw at the port at bufferofs, possibly copying from
+= the port at masterofs.  The EGA version then page flips, while the
+= CGA version updates the screen from the buffer port.
+=
+= Screenpage is the currently displayed page, not the one being drawn
+= Otherpage is the page to be worked with now
+=
+=====================
+*/
+
+void RF_Refresh (void)
+{
+	byte	*newupdate;
+
+	updateptr = updatestart[otherpage];
+
+	RFL_AnimateTiles ();		// DEBUG
+
+//
+// update newly scrolled on tiles and animated tiles from the master screen
+//
+	EGAWRITEMODE(1);
+	EGAMAPMASK(15);
+	RFL_UpdateTiles ();
+	RFL_EraseBlocks ();
+
+//
+// Update is all 0 except where sprites have changed or new area has
+// been scrolled on.  Go through all sprites and update the ones that cover
+// a non 0 update tile
+//
+	EGAWRITEMODE(0);
+	RFL_UpdateSprites ();
+
+//
+// if the main program has a refresh hook set, call their function before
+// displaying the new page
+//
+	if (refreshvector)
+		refreshvector();
+
+//
+// display the changed screen
+//
+	VW_SetScreen(bufferofs+panadjust,panx & xpanmask);
+
+//
+// prepare for next refresh
+//
+// Set the update array to the middle position and clear it out to all "0"s
+// with an UPDATETERMINATE at the end
+//
+	updatestart[otherpage] = newupdate = baseupdatestart[otherpage];
+asm	mov	ax,ds
+asm	mov	es,ax
+asm	xor	ax,ax
+asm	mov	cx,(UPDATESCREENSIZE-2)/2
+asm	mov	di,[newupdate]
+asm	rep	stosw
+asm	mov	[WORD PTR es:di],UPDATETERMINATE
+
+	screenpage ^= 1;
+	otherpage ^= 1;
+	bufferofs = screenstart[otherpage];
+	displayofs = screenstart[screenpage];
+
+//
+// calculate tics since last refresh for adaptive timing
+//
+	RF_CalcTics ();
+}
+
+#endif		// GRMODE == EGAGR
+
+/*
+=============================================================================
+
+					CGA specific routines
+
+=============================================================================
+*/
+
+#if GRMODE == CGAGR
+
+
+/*
+=====================
+=
+= RF_NewPosition   CGA
+=
+=====================
+*/
+
+void RF_NewPosition (unsigned x, unsigned y)
+{
+	int mx,my;
+	byte	*spotptr;
+	unsigned 	updatenum;
+
+	RFL_BoundNewOrigin (x,y);
+
+//
+// clear out all animating tiles
+//
+	RFL_InitAnimList ();
+
+//
+// set up the new update arrays at base position
+//
+	updateptr = baseupdateptr;
+
+	spotptr = updateptr + PORTTILESWIDE;	// used to stick "0"s after rows
+
+	updatenum = 0;				// start at first visable tile
+
+	for (my=0;my<PORTTILESHIGH;my++)
+	{
+		for (mx=0;mx<PORTTILESWIDE;mx++)
+		{
+			RFL_NewTile(updatenum);			// puts "1"s in both pages
+			RFL_CheckForAnimTile(mx+originxtile,my+originytile);
+			updatenum++;
+		}
+		updatenum++;
+		*spotptr = 0; // set a 0 at end of a line of tiles
+		spotptr +=(PORTTILESWIDE+1);
+	}
+	*(word *)(spotptr-PORTTILESWIDE) = UPDATETERMINATE;
+}
+
+
+/*
+=====================
+=
+= RF_Scroll       CGA
+=
+= Move the origin x/y global coordinates, readjust the screen panning, and
+= scroll if needed.  If the scroll distance is greater than one tile, the
+= entire screen will be redrawn (this could be generalized, but scrolling
+= more than one tile per refresh is a bad idea!).
+=
+=====================
+*/
+
+void RF_Scroll (int x, int y)
+{
+	long		neworgx,neworgy;
+	int			i,deltax,deltay,absdx,absdy;
+	int			oldxt,oldyt,move,yy;
+	unsigned	updatespot;
+	byte		*spotptr;
+	unsigned	oldoriginmap,oldscreen,newscreen,screencopy;
+	int			screenmove;
+
+	oldxt = originxtile;
+	oldyt = originytile;
+
+	RFL_BoundScroll (x,y);
+
+	deltax = originxtile - oldxt;
+	absdx = abs(deltax);
+	deltay = originytile - oldyt;
+	absdy = abs(deltay);
+
+	if (absdx>1 || absdy>1)
+	{
+	//
+	// scrolled more than one tile, so start from scratch
+	//
+		RF_NewPosition(originxglobal,originyglobal);
+		return;
+	}
+
+	if (!absdx && !absdy)
+		return;					// the screen has not scrolled an entire tile
+
+
+//
+// float screens
+//
+	screenmove = deltay*16*SCREENWIDTH + deltax*TILEWIDTH;
+	bufferofs += screenmove;
+	masterofs += screenmove;
+
+
+//
+// float the update regions
+//
+	move = deltax;
+	if (deltay==1)
+	  move += UPDATEWIDE;
+	else if (deltay==-1)
+	  move -= UPDATEWIDE;
+
+	updateptr+=move;
+
+//
+// draw the new tiles just scrolled on to the master screen, and
+// mark them as needing to be copied to each screen next refreshes
+// Make sure a zero is at the end of each row in update
+//
+
+	if (deltax)
+	{
+		if (deltax==1)
+		{
+			RFL_NewRow (1);			// new right row
+			RFL_RemoveAnimsOnX (originxtile-1);
+		}
+		else
+		{
+			RFL_NewRow (3);			// new left row
+			RFL_RemoveAnimsOnX (originxtile+PORTTILESWIDE);
+		}
+
+		spotptr = updateptr+PORTTILESWIDE;
+		for	(yy=0;yy<PORTTILESHIGH;yy++)
+		{
+			*spotptr = 0;		// drop a 0 at end of each row
+			spotptr+=UPDATEWIDE;
+		}
+	}
+
+//----------------
+
+	if (deltay)
+	{
+		if (deltay==1)
+		{
+			RFL_NewRow (2);			// new bottom row
+			*(updateptr+UPDATEWIDE*(PORTTILESHIGH-1)+PORTTILESWIDE) = 0;
+			RFL_RemoveAnimsOnY (originytile-1);
+		}
+		else
+		{
+			RFL_NewRow (0);			// new top row
+			*(updateptr+PORTTILESWIDE) = 0;
+			RFL_RemoveAnimsOnY (originytile+PORTTILESHIGH);
+		}
+	}
+
+//----------------
+
+	//
+	// place a new terminator
+	//
+	spotptr = updateptr+UPDATEWIDE*PORTTILESHIGH-1;
+	*spotptr++ = 0;
+	*(unsigned *)spotptr = UPDATETERMINATE;
+}
+
+/*
+=====================
+=
+= RF_PlaceSprite  CGA
+=
+=====================
+*/
+
+void RF_PlaceSprite (void **user,unsigned globalx,unsigned globaly,
+	unsigned spritenumber, drawtype draw, int priority)
+{
+	spritelisttype	register *sprite,*next;
+	spritetabletype far *spr;
+	spritetype _seg	*block;
+	unsigned	shift,pixx;
+	char		str[80],str2[10];
+
+	if (!spritenumber || spritenumber == (unsigned)-1)
+	{
+		RF_RemoveSprite (user);
+		return;
+	}
+
+	sprite = (spritelisttype *)*user;
+
+	if	(sprite)
+	{
+	// sprite allready exists in the list, so we can use it's block
+
+	//
+	// post an erase block to erase the old position by copying
+	// screenx,screeny,width,height
+	//
+		if (!sprite->updatecount)		// may not have been drawn at all yet
+			memcpy (eraselistptr[0]++,sprite,sizeof(eraseblocktype));
+
+		if (priority != sprite->priority)
+		{
+		// sprite moved to another priority, so unlink the old one and
+		// relink it in the new priority
+
+			next = sprite->nextsprite;			// cut old links
+			if (next)
+				next->prevptr = sprite->prevptr;
+			*sprite->prevptr = next;
+			goto linknewspot;
+		}
+	}
+	else
+	{
+	// this is a brand new sprite, so allocate a block from the array
+
+		if (!spritefreeptr)
+			Quit ("RF_PlaceSprite: No free spots in spritearray!");
+
+		sprite = spritefreeptr;
+		spritefreeptr = spritefreeptr->nextsprite;
+
+linknewspot:
+		next = prioritystart[priority];		// stick it in new spot
+		if (next)
+			next->prevptr = &sprite->nextsprite;
+		sprite->nextsprite = next;
+		prioritystart[priority] = sprite;
+		sprite->prevptr = &prioritystart[priority];
+	}
+
+//
+// write the new info to the sprite
+//
+	spr = &spritetable[spritenumber-STARTSPRITES];
+	block = (spritetype _seg *)grsegs[spritenumber];
+
+	if (!block)
+	{
+		strcpy (str,"RF_PlaceSprite: Placed an uncached sprite!");
+		itoa (spritenumber,str2,10);
+		strcat (str,str2);
+		Quit (str);
+	}
+
+
+	globaly+=spr->orgy;
+	globalx+=spr->orgx;
+
+	sprite->screenx = globalx >> G_CGASX_SHIFT;
+	sprite->screeny = globaly >> G_SY_SHIFT;
+	sprite->width = block->width[0];
+	sprite->height = spr->height;
+	sprite->grseg = spritenumber;
+	sprite->sourceofs = block->sourceoffset[0];
+	sprite->planesize = block->planesize[0];
+	sprite->draw = draw;
+	sprite->priority = priority;
+	sprite->tilex = sprite->screenx >> SX_T_SHIFT;
+	sprite->tiley = sprite->screeny >> SY_T_SHIFT;
+	sprite->tilewide = ( (sprite->screenx + sprite->width -1) >> SX_T_SHIFT )
+		- sprite->tilex + 1;
+	sprite->tilehigh = ( (sprite->screeny + sprite->height -1) >> SY_T_SHIFT )
+		- sprite->tiley + 1;
+
+	sprite->updatecount = 1;		// draw on next refresh
+
+// save the sprite pointer off in the user's pointer so it can be moved
+// again later
+
+	*user = sprite;
+}
+
+//===========================================================================
+
+/*
+=====================
+=
+= RF_RemoveSprite CGA
+=
+=====================
+*/
+
+void RF_RemoveSprite (void **user)
+{
+	spritelisttype	*sprite,*next;
+
+	sprite = (spritelisttype *)*user;
+	if (!sprite)
+		return;
+
+//
+// post an erase block to erase the old position by copying
+// screenx,screeny,width,height
+//
+	if (!sprite->updatecount)
+	{
+		memcpy (eraselistptr[0]++,sprite,sizeof(eraseblocktype));
+	}
+
+//
+// unlink the sprite node
+//
+	next = sprite->nextsprite;
+	if (next)						// if (!next), sprite is last in chain
+		next->prevptr = sprite->prevptr;
+	*sprite->prevptr = next;
+
+//
+// add it back to the free list
+//
+	sprite->nextsprite = spritefreeptr;
+	spritefreeptr = sprite;
+
+//
+// null the users pointer, so next time that actor gets placed, it will
+// allocate a new block
+//
+
+	*user = 0;
+}
+
+
+/*
+====================
+=
+= RFL_EraseBlocks CGA
+=
+= Write mode 1 should be set
+=
+====================
+*/
+
+void RFL_EraseBlocks (void)
+{
+	eraseblocktype	*block,*done;
+	int			screenxh,screenyh;
+	unsigned	pos,xtl,ytl,xth,yth,x,y;
+	byte		*updatespot;
+	unsigned	updatedelta;
+
+	block = &eraselist[0][0];
+
+	done = eraselistptr[0];
+
+	while (block != done)
+	{
+
+	//
+	// clip the block to the current screen view
+	//
+		block->screenx -= originxscreen;
+		block->screeny -= originyscreen;
+
+		if (block->screenx < 0)
+		{
+			block->width += block->screenx;
+			if (block->width<1)
+				goto next;
+			block->screenx = 0;
+		}
+
+		if (block->screeny < 0)
+		{
+			block->height += block->screeny;
+			if (block->height<1)
+				goto next;
+			block->screeny = 0;
+		}
+
+		screenxh = block->screenx + block->width;
+		screenyh = block->screeny + block->height;
+
+		if (screenxh > CGAPORTSCREENWIDE)
+		{
+			block->width = CGAPORTSCREENWIDE-block->screenx;
+			screenxh = block->screenx + block->width;
+		}
+
+		if (screenyh > PORTSCREENHIGH)
+		{
+			block->height = PORTSCREENHIGH-block->screeny;
+			screenyh = block->screeny + block->height;
+		}
+
+		if (block->width<1 || block->height<1)
+			goto next;
+
+	//
+	// erase the block by copying from the master screen
+	//
+		pos = ylookup[block->screeny]+block->screenx;
+		block->width = (block->width + (pos&1) + 1)& ~1;
+		pos &= ~1;				// make sure a word copy gets used
+		VW_ScreenToScreen (masterofs+pos,bufferofs+pos,
+			block->width,block->height);
+
+	//
+	// put 2s in update where the block was, to force sprites to update
+	//
+		xtl = block->screenx >> SX_T_SHIFT;
+		xth = (block->screenx+block->width-1) >> SX_T_SHIFT;
+		ytl = block->screeny >> SY_T_SHIFT;
+		yth = (block->screeny+block->height-1) >> SY_T_SHIFT;
+
+		updatespot = updateptr + uwidthtable[ytl] + xtl;
+		updatedelta = UPDATEWIDE - (xth-xtl+1);
+
+		for (y=ytl;y<=yth;y++)
+		{
+			for (x=xtl;x<=xth;x++)
+				*updatespot++ = 2;
+			updatespot += updatedelta;		// down to next line
+		}
+
+next:
+		block++;
+	}
+	eraselistptr[0] = &eraselist[0][0];
+}
+
+
+/*
+====================
+=
+= RFL_UpdateSprites      CGA
+=
+= NOTE: Implement vertical clipping!
+=
+====================
+*/
+
+void RFL_UpdateSprites (void)
+{
+	spritelisttype	*sprite;
+	int	portx,porty,x,y,xtl,xth,ytl,yth;
+	int	priority;
+	unsigned dest;
+	byte		*updatespot,*baseupdatespot;
+	unsigned	updatedelta;
+
+	unsigned	updatecount;
+	unsigned	height,sourceofs;
+
+#ifdef PROFILE
+	updatecount = 0;
+#endif
+
+
+	for (priority=0;priority<PRIORITIES;priority++)
+	{
+		if (priority==MASKEDTILEPRIORITY)
+			RFL_MaskForegroundTiles ();
+
+		for (sprite = prioritystart[priority]; sprite ;
+			sprite = (spritelisttype *)sprite->nextsprite)
+		{
+		//
+		// see if the sprite has any visable area in the port
+		//
+
+			portx = sprite->screenx - originxscreen;
+			porty = sprite->screeny - originyscreen;
+			xtl = portx >> SX_T_SHIFT;
+			xth = (portx + sprite->width-1) >> SX_T_SHIFT;
+			ytl = porty >> SY_T_SHIFT;
+			yth = (porty + sprite->height-1) >> SY_T_SHIFT;
+
+			if (xtl<0)
+			  xtl = 0;
+			if (xth>=PORTTILESWIDE)
+			  xth = PORTTILESWIDE-1;
+			if (ytl<0)
+			  ytl = 0;
+			if (yth>=PORTTILESHIGH)
+			  yth = PORTTILESHIGH-1;
+
+			if (xtl>xth || ytl>yth)
+				continue;
+
+		//
+		// see if it's visable area covers any non 0 update tiles
+		//
+			updatespot = baseupdatespot = updateptr + uwidthtable[ytl] + xtl;
+			updatedelta = UPDATEWIDE - (xth-xtl+1);
+
+			if (sprite->updatecount)
+			{
+				sprite->updatecount--;			// the sprite was just placed,
+				goto redraw;					// so draw it for sure
+			}
+
+			for (y=ytl;y<=yth;y++)
+			{
+				for (x=xtl;x<=xth;x++)
+					if (*updatespot++)
+						goto redraw;
+				updatespot += updatedelta;		// down to next line
+			}
+			continue;							// no need to update
+
+redraw:
+		//
+		// set the tiles it covers to 3, because those tiles are being
+		// updated
+		//
+			updatespot = baseupdatespot;
+			for (y=ytl;y<=yth;y++)
+			{
+				for (x=xtl;x<=xth;x++)
+					*updatespot++ = 3;
+				updatespot += updatedelta;		// down to next line
+			}
+		//
+		// draw it!
+		//
+			height = sprite->height;
+			sourceofs = sprite->sourceofs;
+			if (porty<0)
+			{
+				height += porty;					// clip top off
+				sourceofs -= porty*sprite->width;
+				porty = 0;
+			}
+			else if (porty+height>PORTSCREENHIGH)
+			{
+				height = PORTSCREENHIGH - porty;    // clip bottom off
+			}
+
+			dest = bufferofs + ylookup[porty] + portx;
+
+			switch (sprite->draw)
+			{
+			case spritedraw:
+				VW_MaskBlock(grsegs[sprite->grseg], sourceofs,
+					dest,sprite->width,height,sprite->planesize);
+				break;
+
+			case maskdraw:
+				VW_InverseMask(grsegs[sprite->grseg], sourceofs,
+					dest,sprite->width,height);
+				break;
+
+			}
+#ifdef PROFILE
+			updatecount++;
+#endif
+
+
+		}
+	}
+}
+
+
+/*
+=====================
+=
+= RF_Refresh        CGA
+=
+= All routines will draw at the port at bufferofs, possibly copying from
+= the port at masterofs.  The EGA version then page flips, while the
+= CGA version updates the screen from the buffer port.
+=
+= Screenpage is the currently displayed page, not the one being drawn
+= Otherpage is the page to be worked with now
+=
+=====================
+*/
+
+void RF_Refresh (void)
+{
+	long newtime,oldtimecount;
+
+	RFL_AnimateTiles ();
+
+//
+// update newly scrolled on tiles and animated tiles from the master screen
+//
+	RFL_UpdateTiles ();
+	RFL_EraseBlocks ();
+
+//
+// Update is all 0 except where sprites have changed or new area has
+// been scrolled on.  Go through all sprites and update the ones that cover
+// a non 0 update tile
+//
+	RFL_UpdateSprites ();
+
+//
+// if the main program has a refresh hook set, call their function before
+// displaying the new page
+//
+	if (refreshvector)
+		refreshvector();
+
+//
+// update everything to the screen
+//
+	VW_CGAFullUpdate ();
+
+//
+// calculate tics since last refresh for adaptive timing
+//
+	RF_CalcTics ();
+}
+
+#endif		// GRMODE == CGAGR
diff --git a/16/keen456/KEEN4-6/ID_RF.H b/16/keen456/KEEN4-6/ID_RF.H
new file mode 100755
index 00000000..5648034b
--- /dev/null
+++ b/16/keen456/KEEN4-6/ID_RF.H
@@ -0,0 +1,169 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+// ID_RF.H
+
+#define __ID_RF__
+
+#ifndef __ID_MM__
+#include "ID_MM.H"
+#endif
+
+/*
+=============================================================================
+
+							CONSTANTS
+
+=============================================================================
+*/
+
+#define	MINTICS				2
+#define	MAXTICS				5
+#define DEMOTICS			3
+
+#define	MAPBORDER			2		// map border must be at least 1
+
+#ifdef KEEN5
+
+#define	MAXSPRITES			60		// max tracked sprites
+#define	MAXANIMTILES		90		// max animating tiles on screen
+#define MAXANIMTYPES		80		// max different unique anim tiles on map
+
+#define	MAXMAPHEIGHT		250
+
+#else
+
+#define	MAXSPRITES			60		// max tracked sprites
+#define	MAXANIMTILES		90		// max animating tiles on screen
+#define MAXANIMTYPES		65		// max different unique anim tiles on map
+
+#define	MAXMAPHEIGHT		200
+
+#endif
+
+#define	PRIORITIES			4
+#define	MASKEDTILEPRIORITY	3		// planes go: 0,1,2,MTILES,3
+
+#define TILEGLOBAL			256
+#define PIXGLOBAL			16
+
+#define	G_T_SHIFT			8		// global >> ?? = tile
+#define	G_P_SHIFT			4		// global >> ?? = pixels
+#define P_T_SHIFT			4		// pixels >> ?? = tile
+
+#define	PORTTILESWIDE		21      // all drawing takes place inside a
+#define	PORTTILESHIGH		14		// non displayed port of this size
+
+//#define	PORTGLOBALWIDE		(21*TILEGLOBAL)
+//#define	PORTGLOBALHIGH		(14*TILEGLOBAL)
+
+#define UPDATEWIDE			(PORTTILESWIDE+1)
+#define UPDATEHIGH			PORTTILESHIGH
+
+
+//===========================================================================
+
+typedef enum {spritedraw,maskdraw} drawtype;
+
+/*
+=============================================================================
+
+						 PUBLIC VARIABLES
+
+=============================================================================
+*/
+
+
+extern	boolean		compatability;			// crippled refresh for wierdo SVGAs
+
+extern	unsigned	tics;
+extern	long		lasttimecount;
+
+extern	unsigned	originxglobal,originyglobal;
+extern	unsigned	originxtile,originytile;
+extern	unsigned	originxscreen,originyscreen;
+
+extern	unsigned	mapwidth,mapheight,mapbyteswide,mapwordswide
+					,mapbytesextra,mapwordsextra;
+extern	unsigned	mapbwidthtable[MAXMAPHEIGHT];
+
+extern	unsigned	originxmin,originxmax,originymin,originymax;
+
+extern	unsigned	masterofs;
+
+//
+// the floating update window is also used by the view manager for
+// double buffer tracking
+//
+
+extern	byte		*updateptr;				// current start of update window
+
+#if GRMODE == CGAGR
+extern	byte		*baseupdateptr;
+#endif
+
+extern unsigned	blockstarts[UPDATEWIDE*UPDATEHIGH];
+extern unsigned	updatemapofs[UPDATEWIDE*UPDATEHIGH];
+extern unsigned	uwidthtable[UPDATEHIGH];		// lookup instead of multiple
+
+#define	UPDATETERMINATE	0x0301
+
+/*
+=============================================================================
+
+						 PUBLIC FUNCTIONS
+
+=============================================================================
+*/
+
+void RF_Startup (void);
+void RF_Shutdown (void);
+
+void RF_FixOfs (void);
+void RF_NewMap (void);
+void RF_MarkTileGraphics (void);
+void RF_SetScrollBlock (int x, int y, boolean horizontal);
+void RF_NewPosition (unsigned x, unsigned y);
+void RF_Scroll (int x, int y);
+
+void RF_MapToMap (unsigned srcx, unsigned srcy,
+				  unsigned destx, unsigned desty,
+				  unsigned width, unsigned height);
+void RF_MemToMap (unsigned far *source, unsigned plane,
+				  unsigned destx, unsigned desty,
+				  unsigned width, unsigned height);
+
+void RF_ClearBlock (int	x, int y, int width, int height);
+void RF_RedrawBlock (int x, int y, int width, int height);
+
+void RF_PlaceSprite (void **user,unsigned globalx,unsigned globaly,
+	unsigned spritenumber, drawtype draw, int priority);
+void RF_RemoveSprite (void **user);
+
+void RF_CalcTics (void);
+
+void RF_Refresh (void);
+void RF_ForceRefresh (void);
+void RF_SetRefreshHook (void (*func) (void) );
+
+unsigned RF_FindFreeBuffer (void);
+
diff --git a/16/keen456/KEEN4-6/ID_RF_A.ASM b/16/keen456/KEEN4-6/ID_RF_A.ASM
new file mode 100755
index 00000000..56db0c77
--- /dev/null
+++ b/16/keen456/KEEN4-6/ID_RF_A.ASM
@@ -0,0 +1,690 @@
+; Catacomb 3-D Source Code
+; Copyright (C) 1993-2014 Flat Rock Software
+;
+; This program is free software; you can redistribute it and/or modify
+; it under the terms of the GNU General Public License as published by
+; the Free Software Foundation; either version 2 of the License, or
+; (at your option) any later version.
+;
+; This program is distributed in the hope that it will be useful,
+; but WITHOUT ANY WARRANTY; without even the implied warranty of
+; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+; GNU General Public License for more details.
+;
+; You should have received a copy of the GNU General Public License along
+; with this program; if not, write to the Free Software Foundation, Inc.,
+; 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+
+; ID_RF_A.ASM
+
+IDEAL
+MODEL	MEDIUM,C
+
+INCLUDE	"ID_ASM.EQU"
+
+;============================================================================
+
+TILESWIDE	=	21
+TILESHIGH	=	14
+
+UPDATESIZE	=	(TILESWIDE+1)*TILESHIGH+1
+
+DATASEG
+
+EXTRN	screenseg:WORD
+EXTRN	updateptr:WORD
+EXTRN	updatestart:WORD
+EXTRN	masterofs:WORD		;start of master tile port
+EXTRN	bufferofs:WORD		;start of current buffer port
+EXTRN	screenstart:WORD	;starts of three screens (0/1/master) in EGA mem
+EXTRN	grsegs:WORD
+EXTRN	mapsegs:WORD
+EXTRN	originmap:WORD
+EXTRN	updatemapofs:WORD
+EXTRN	tinf:WORD			;seg pointer to map header and tile info
+EXTRN	blockstarts:WORD	;offsets from bufferofs for each update block
+
+planemask	db	?
+planenum	db	?
+
+CODESEG
+
+screenstartcs	dw	?		;in code segment for accesability
+
+
+
+
+IFE GRMODE-CGAGR
+;============================================================================
+;
+; CGA refresh routines
+;
+;============================================================================
+
+TILEWIDTH	=	4
+
+;=================
+;
+; RFL_NewTile
+;
+; Draws a composit two plane tile to the master screen and sets the update
+; spot to 1 in both update pages, forcing the tile to be copied to the
+; view pages the next two refreshes
+;
+; Called to draw newlly scrolled on strips and animating tiles
+;
+;=================
+
+PROC	RFL_NewTile	updateoffset:WORD
+PUBLIC	RFL_NewTile
+USES	SI,DI
+
+;
+; mark both update lists at this spot
+;
+	mov	di,[updateoffset]
+
+	mov	bx,[updateptr]			;start of update matrix
+	mov	[BYTE bx+di],1
+
+	mov	dx,SCREENWIDTH-TILEWIDTH		;add to get to start of next line
+
+;
+; set di to the location in screenseg to draw the tile
+;
+	shl	di,1
+	mov	si,[updatemapofs+di]	;offset in map from origin
+	add	si,[originmap]
+	mov	di,[blockstarts+di]		;screen location for tile
+	add	di,[masterofs]
+
+;
+; set BX to the foreground tile number and SI to the background number
+; If either BX or SI = 0xFFFF, the tile does not need to be masked together
+; as one of the planes totally eclipses the other
+;
+	mov	es,[mapsegs+2]			;foreground plane
+	mov	bx,[es:si]
+	mov	es,[mapsegs]			;background plane
+	mov	si,[es:si]
+
+	mov	es,[screenseg]
+
+	or	bx,bx
+	jz	@@singletile
+	jmp	@@maskeddraw			;draw both together
+
+;=============
+;
+; Draw single background tile from main memory
+;
+;=============
+
+@@singletile:
+	shl	si,1
+	mov	ds,[grsegs+STARTTILE16*2+si]
+
+	xor	si,si					;block is segment aligned
+
+REPT	15
+	movsw
+	movsw
+	add	di,dx
+ENDM
+	movsw
+	movsw
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+	ret
+
+
+;=========
+;
+; Draw a masked tile combo
+; Interupts are disabled and the stack segment is reassigned
+;
+;=========
+@@maskeddraw:
+	cli							; don't allow ints when SS is set
+	shl	bx,1
+	mov	ss,[grsegs+STARTTILE16M*2+bx]
+	shl	si,1
+	mov	ds,[grsegs+STARTTILE16*2+si]
+
+	xor	si,si					;first word of tile data
+
+REPT	16
+	mov	ax,[si]					;background tile
+	and	ax,[ss:si]				;mask
+	or	ax,[ss:si+64]			;masked data
+	stosw
+	mov	ax,[si+2]				;background tile
+	and	ax,[ss:si+2]			;mask
+	or	ax,[ss:si+66]			;masked data
+	stosw
+	add	si,4
+	add	di,dx
+ENDM
+
+	mov	ax,@DATA
+	mov	ss,ax
+	sti
+	mov	ds,ax
+	ret
+ENDP
+
+ENDIF
+
+
+
+IFE GRMODE-EGAGR
+;===========================================================================
+;
+; EGA refresh routines
+;
+;===========================================================================
+
+TILEWIDTH	=	2
+
+;=================
+;
+; RFL_NewTile
+;
+; Draws a composit two plane tile to the master screen and sets the update
+; spot to 1 in both update pages, forcing the tile to be copied to the
+; view pages the next two refreshes
+;
+; Called to draw newlly scrolled on strips and animating tiles
+;
+; Assumes write mode 0
+;
+;=================
+
+PROC	RFL_NewTile	updateoffset:WORD
+PUBLIC	RFL_NewTile
+USES	SI,DI
+
+;
+; mark both update lists at this spot
+;
+	mov	di,[updateoffset]
+
+	mov	bx,[updatestart]		;page 0 pointer
+	mov	[BYTE bx+di],1
+	mov	bx,[updatestart+2]		;page 1 pointer
+	mov	[BYTE bx+di],1
+
+;
+; set screenstartcs to the location in screenseg to draw the tile
+;
+	shl	di,1
+	mov	si,[updatemapofs+di]	;offset in map from origin
+	add	si,[originmap]
+	mov	di,[blockstarts+di]		;screen location for tile
+	add	di,[masterofs]
+	mov	[cs:screenstartcs],di
+
+;
+; set BX to the foreground tile number and SI to the background number
+; If either BX or SI = 0xFFFF, the tile does not need to be masked together
+; as one of the planes totally eclipses the other
+;
+	mov	es,[mapsegs+2]			;foreground plane
+	mov	bx,[es:si]
+	mov	es,[mapsegs]			;background plane
+	mov	si,[es:si]
+
+	mov	es,[screenseg]
+	mov	dx,SC_INDEX				;for stepping through map mask planes
+
+	or	bx,bx
+	jz	@@singletile
+	jmp	@@maskeddraw			;draw both together
+
+;=========
+;
+; No foreground tile, so draw a single background tile.
+;
+;=========
+@@singletile:
+
+	mov	bx,SCREENWIDTH-2		;add to get to start of next line
+	shl	si,1
+
+	mov	ax,[cs:screenstartcs]
+	mov	ds,[grsegs+STARTTILE16*2+si]
+
+	xor	si,si					;block is segment aligned
+
+	mov	ax,SC_MAPMASK+0001b*256	;map mask for plane 0
+
+	mov	cx,4					;draw four planes
+@@planeloop:
+	mov	dx,SC_INDEX
+	WORDOUT
+
+	mov	di,[cs:screenstartcs]	;start at same place in all planes
+
+REPT	15
+	movsw
+	add	di,bx
+ENDM
+	movsw
+
+	shl	ah,1					;shift plane mask over for next plane
+	loop	@@planeloop
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+	ret
+
+
+;=========
+;
+; Draw a masked tile combo
+; Interupts are disabled and the stack segment is reassigned
+;
+;=========
+@@maskeddraw:
+	cli							; don't allow ints when SS is set
+	shl	bx,1
+	mov	ss,[grsegs+STARTTILE16M*2+bx]
+	shl	si,1
+	mov	ds,[grsegs+STARTTILE16*2+si]
+
+	xor	si,si					;first word of tile data
+
+	mov	ax,SC_MAPMASK+0001b*256	;map mask for plane 0
+
+	mov	di,[cs:screenstartcs]
+@@planeloopm:
+	WORDOUT
+tileofs		=	0
+lineoffset	=	0
+REPT	16
+	mov	bx,[si+tileofs]			;background tile
+	and	bx,[ss:tileofs]			;mask
+	or	bx,[ss:si+tileofs+32]	;masked data
+	mov	[es:di+lineoffset],bx
+tileofs		=	tileofs + 2
+lineoffset	=	lineoffset + SCREENWIDTH
+ENDM
+	add	si,32
+	shl	ah,1					;shift plane mask over for next plane
+	cmp	ah,10000b
+	je	@@done					;drawn all four planes
+	jmp	@@planeloopm
+
+@@done:
+	mov	ax,@DATA
+	mov	ss,ax
+	sti
+	mov	ds,ax
+	ret
+ENDP
+
+ENDIF
+
+IFE GRMODE-VGAGR
+;============================================================================
+;
+; VGA refresh routines
+;
+;============================================================================
+
+
+ENDIF
+
+
+;============================================================================
+;
+; reasonably common refresh routines
+;
+;============================================================================
+
+
+;=================
+;
+; RFL_UpdateTiles
+;
+; Scans through the update matrix pointed to by updateptr, looking for 1s.
+; A 1 represents a tile that needs to be copied from the master screen to the
+; current screen (a new row or an animated tiled).  If more than one adjacent
+; tile in a horizontal row needs to be copied, they will be copied as a group.
+;
+; Assumes write mode 1
+;
+;=================
+
+
+; AX	0/1 for scasb, temp for segment register transfers
+; BX    width for block copies
+; CX	REP counter
+; DX	line width deltas
+; SI	source for copies
+; DI	scas dest / movsb dest
+; BP	pointer to UPDATETERMINATE
+;
+; DS
+; ES
+; SS
+
+PROC	RFL_UpdateTiles
+PUBLIC	RFL_UpdateTiles
+USES	SI,DI,BP
+
+	jmp	SHORT @@realstart
+@@done:
+;
+; all tiles have been scanned
+;
+	ret
+
+@@realstart:
+	mov	di,[updateptr]
+	mov	bp,(TILESWIDE+1)*TILESHIGH+1
+	add	bp,di					; when di = bx, all tiles have been scanned
+	push	di
+	mov	cx,-1					; definately scan the entire thing
+
+;
+; scan for a 1 in the update list, meaning a tile needs to be copied
+; from the master screen to the current screen
+;
+@@findtile:
+	pop	di						; place to continue scaning from
+	mov	ax,ss
+	mov	es,ax					; search in the data segment
+	mov	ds,ax
+	mov al,1
+	repne	scasb
+	cmp	di,bp
+	je	@@done
+
+	cmp	[BYTE di],al
+	jne	@@singletile
+	jmp	@@tileblock
+
+;============
+;
+; copy a single tile
+;
+;============
+EVEN
+@@singletile:
+	inc	di						; we know the next tile is nothing
+	push	di					; save off the spot being scanned
+	sub	di,[updateptr]
+	shl	di,1
+	mov	di,[blockstarts-4+di]	; start of tile location on screen
+	mov	si,di
+	add	di,[bufferofs]			; dest in current screen
+	add	si,[masterofs]			; source in master screen
+
+	mov	dx,SCREENWIDTH-TILEWIDTH
+	mov	ax,[screenseg]
+	mov	ds,ax
+	mov	es,ax
+
+;--------------------------
+
+IFE GRMODE-CGAGR
+
+REPT	15
+	movsw
+	movsw
+	add	si,dx
+	add	di,dx
+ENDM
+	movsw
+	movsw
+
+ENDIF
+
+;--------------------------
+
+IFE GRMODE-EGAGR
+
+REPT	15
+	movsb
+	movsb
+	add	si,dx
+	add	di,dx
+ENDM
+	movsb
+	movsb
+
+ENDIF
+
+;--------------------------
+
+	jmp	@@findtile
+
+;============
+;
+; more than one tile in a row needs to be updated, so do it as a group
+;
+;============
+EVEN
+@@tileblock:
+	mov	dx,di					; hold starting position + 1 in dx
+	inc	di						; we know the next tile also gets updated
+	repe	scasb				; see how many more in a row
+	push	di					; save off the spot being scanned
+
+	mov	bx,di
+	sub	bx,dx					; number of tiles in a row
+	shl	bx,1					; number of bytes / row
+
+	mov	di,dx					; lookup position of start tile
+	sub	di,[updateptr]
+	shl	di,1
+	mov	di,[blockstarts-2+di]	; start of tile location
+	mov	si,di
+	add	di,[bufferofs]			; dest in current screen
+	add	si,[masterofs]			; source in master screen
+
+	mov	dx,SCREENWIDTH
+	sub	dx,bx					; offset to next line on screen
+IFE GRMODE-CGAGR
+	sub	dx,bx					; bx is words wide in CGA tiles
+ENDIF
+
+	mov	ax,[screenseg]
+	mov	ds,ax
+	mov	es,ax
+
+REPT	15
+	mov	cx,bx
+IFE GRMODE-CGAGR
+	rep	movsw
+ENDIF
+IFE GRMODE-EGAGR
+	rep	movsb
+ENDIF
+	add	si,dx
+	add	di,dx
+ENDM
+	mov	cx,bx
+IFE GRMODE-CGAGR
+	rep	movsw
+ENDIF
+IFE GRMODE-EGAGR
+	rep	movsb
+ENDIF
+
+	dec	cx						; was 0 from last rep movsb, now $ffff for scasb
+	jmp	@@findtile
+
+ENDP
+
+
+;============================================================================
+
+
+;=================
+;
+; RFL_MaskForegroundTiles
+;
+; Scan through update looking for 3's.  If the foreground tile there is a
+; masked foreground tile, draw it to the screen
+;
+;=================
+
+PROC	RFL_MaskForegroundTiles
+PUBLIC	RFL_MaskForegroundTiles
+USES	SI,DI,BP
+	jmp	SHORT @@realstart
+@@done:
+;
+; all tiles have been scanned
+;
+	ret
+
+@@realstart:
+	mov	di,[updateptr]
+	mov	bp,(TILESWIDE+1)*TILESHIGH+2
+	add	bp,di					; when di = bx, all tiles have been scanned
+	push	di
+	mov	cx,-1					; definately scan the entire thing
+;
+; scan for a 3 in the update list
+;
+@@findtile:
+	mov	ax,ss
+	mov	es,ax					; scan in the data segment
+	mov	al,3
+	pop	di						; place to continue scaning from
+	repne	scasb
+	cmp	di,bp
+	je	@@done
+
+;============
+;
+; found a tile, see if it needs to be masked on
+;
+;============
+
+	push	di
+
+	sub	di,[updateptr]
+	shl	di,1
+	mov	si,[updatemapofs-2+di]	; offset from originmap
+	add	si,[originmap]
+
+	mov	es,[mapsegs+2]			; foreground map plane segment
+	mov	si,[es:si]				; foreground tile number
+
+	or	si,si
+	jz	@@findtile				; 0 = no foreground tile
+
+	mov	bx,si
+	add	bx,INTILE				;INTILE tile info table
+	mov	es,[tinf]
+	test	[BYTE PTR es:bx],80h		;high bit = masked tile
+	jz	@@findtile
+
+;-------------------
+
+IFE GRMODE-CGAGR
+;=================
+;
+; mask the tile CGA
+;
+;=================
+
+	mov	di,[blockstarts-2+di]
+	add	di,[bufferofs]
+	mov	es,[screenseg]
+	shl	si,1
+	mov	ds,[grsegs+STARTTILE16M*2+si]
+
+	mov	bx,64					;data starts 64 bytes after mask
+
+	xor	si,si
+
+lineoffset	=	0
+REPT	16
+	mov	ax,[es:di+lineoffset]	;background
+	and	ax,[si]					;mask
+	or	ax,[si+bx]				;masked data
+	mov	[es:di+lineoffset],ax	;background
+	inc	si
+	inc	si
+	mov	ax,[es:di+lineoffset+2]	;background
+	and	ax,[si]					;mask
+	or	ax,[si+bx]				;masked data
+	mov	[es:di+lineoffset+2],ax	;background
+	inc	si
+	inc	si
+lineoffset	=	lineoffset + SCREENWIDTH
+ENDM
+ENDIF
+
+;-------------------
+
+IFE GRMODE-EGAGR
+;=================
+;
+; mask the tile
+;
+;=================
+
+	mov	[BYTE planemask],1
+	mov	[BYTE planenum],0
+
+	mov	di,[blockstarts-2+di]
+	add	di,[bufferofs]
+	mov	[cs:screenstartcs],di
+	mov	es,[screenseg]
+	shl	si,1
+	mov	ds,[grsegs+STARTTILE16M*2+si]
+
+	mov	bx,32					;data starts 32 bytes after mask
+
+@@planeloopm:
+	mov	dx,SC_INDEX
+	mov	al,SC_MAPMASK
+	mov	ah,[ss:planemask]
+	WORDOUT
+	mov	dx,GC_INDEX
+	mov	al,GC_READMAP
+	mov	ah,[ss:planenum]
+	WORDOUT
+
+	xor	si,si
+	mov	di,[cs:screenstartcs]
+lineoffset	=	0
+REPT	16
+	mov	cx,[es:di+lineoffset]	;background
+	and	cx,[si]					;mask
+	or	cx,[si+bx]				;masked data
+	inc	si
+	inc	si
+	mov	[es:di+lineoffset],cx
+lineoffset	=	lineoffset + SCREENWIDTH
+ENDM
+	add	bx,32					;the mask is now further away
+	inc	[ss:planenum]
+	shl	[ss:planemask],1		;shift plane mask over for next plane
+	cmp	[ss:planemask],10000b	;done all four planes?
+	je	@@drawn					;drawn all four planes
+	jmp	@@planeloopm
+
+@@drawn:
+ENDIF
+
+;-------------------
+
+	mov	ax,ss
+	mov	ds,ax
+	mov	cx,-1					;definately scan the entire thing
+
+	jmp	@@findtile
+
+ENDP
+
+
+END
+
diff --git a/16/keen456/KEEN4-6/ID_SD.C b/16/keen456/KEEN4-6/ID_SD.C
new file mode 100755
index 00000000..91f1ba75
--- /dev/null
+++ b/16/keen456/KEEN4-6/ID_SD.C
@@ -0,0 +1,1336 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+//
+//	ID Engine
+//	ID_SD.c - Sound Manager
+//	v1.1d1
+//	By Jason Blochowiak
+//
+
+//
+//	This module handles dealing with generating sound on the appropriate
+//		hardware
+//
+//	Depends on: User Mgr (for parm checking)
+//
+//	Globals:
+//		For User Mgr:
+//			SoundSourcePresent - Sound Source thingie present?
+//			SoundBlasterPresent - SoundBlaster card present?
+//			AdLibPresent - AdLib card present?
+//			SoundMode - What device is used for sound effects
+//				(Use SM_SetSoundMode() to set)
+//			MusicMode - What device is used for music
+//				(Use SM_SetMusicMode() to set)
+//		For Cache Mgr:
+//			NeedsDigitized - load digitized sounds?
+//			NeedsMusic - load music?
+//
+
+#pragma hdrstop		// Wierdo thing with MUSE
+
+#include <dos.h>
+
+#ifdef	_MUSE_      // Will be defined in ID_Types.h
+#include "ID_SD.h"
+#else
+#include "ID_HEADS.H"
+#endif
+#pragma	hdrstop
+#pragma	warn	-pia
+
+#define	SDL_SoundFinished()	{SoundNumber = SoundPriority = 0;}
+
+// Macros for AdLib stuff
+#define	selreg(n)	outportb(0x388,n)
+#define	writereg(n)	outportb(0x389,n)
+#define	readstat()	inportb(0x388)
+
+//	Global variables
+	boolean		SoundSourcePresent,SoundBlasterPresent,AdLibPresent,QuietFX,
+				NeedsDigitized,NeedsMusic;
+	SDMode		SoundMode;
+	SMMode		MusicMode;
+	longword	TimeCount;
+	word		HackCount;
+	word		*SoundTable;	// Really * _seg *SoundTable, but that don't work
+	boolean		ssIsTandy;
+	word		ssPort = 2;
+
+//	Internal variables
+static	boolean			SD_Started;
+static	boolean			TimerDone;
+static	word			TimerVal,TimerDelay10,TimerDelay25,TimerDelay100;
+static	longword		TimerDivisor,TimerCount;
+static	char			*ParmStrings[] =
+						{
+							"noal",
+							"adlib",
+							nil
+						};
+static	void			(*SoundUserHook)(void);
+static	word			SoundNumber,SoundPriority;
+static	void interrupt	(*t0OldService)(void);
+//static	word			t0CountTable[] = {8,8,8,8,40,40};
+static	long			LocalTime;
+
+//	PC Sound variables
+static	byte			pcLastSample,far *pcSound;
+static	longword		pcLengthLeft;
+static	word			pcSoundLookup[255];
+
+//	AdLib variables
+static	boolean			alNoCheck;
+static	byte			far *alSound;
+static	word			alBlock;
+static	longword		alLengthLeft;
+static	longword		alTimeCount;
+static	Instrument		alZeroInst;
+
+// This table maps channel numbers to carrier and modulator op cells
+static	byte			carriers[9] =  { 3, 4, 5,11,12,13,19,20,21},
+						modifiers[9] = { 0, 1, 2, 8, 9,10,16,17,18},
+// This table maps percussive voice numbers to op cells
+						pcarriers[5] = {19,0xff,0xff,0xff,0xff},
+						pmodifiers[5] = {16,17,18,20,21};
+
+//	Sequencer variables
+static	boolean			sqActive;
+static	word			alFXReg;
+static	ActiveTrack		*tracks[sqMaxTracks],
+						mytracks[sqMaxTracks];
+static	word			sqMode,sqFadeStep;
+static	word			far *sqHack,far *sqHackPtr,sqHackLen,sqHackSeqLen;
+static	long			sqHackTime;
+
+//	Internal routines
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SDL_SetTimer0() - Sets system timer 0 to the specified speed
+//
+///////////////////////////////////////////////////////////////////////////
+#pragma	argsused
+static void
+SDL_SetTimer0(word speed)
+{
+#ifndef TPROF	// If using Borland's profiling, don't screw with the timer
+	outportb(0x43,0x36);				// Change timer 0
+	outportb(0x40,speed);
+	outportb(0x40,speed >> 8);
+	TimerDivisor = speed;
+#else
+	TimerDivisor = 0x10000;
+#endif
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SDL_SetIntsPerSec() - Uses SDL_SetTimer0() to set the number of
+//		interrupts generated by system timer 0 per second
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+SDL_SetIntsPerSec(word ints)
+{
+	SDL_SetTimer0(1192030 / ints);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SDL_TimingService() - Used by SDL_InitDelay() to determine a timing
+//		value for the current system that we're running on
+//
+///////////////////////////////////////////////////////////////////////////
+static void interrupt
+SDL_TimingService(void)
+{
+	TimerVal = _CX;
+	TimerDone++;
+
+	outportb(0x20,0x20);				// Ack interrupt
+}
+
+#if 0
+///////////////////////////////////////////////////////////////////////////
+//
+//	SDL_InitDelay() - Sets up TimerDelay's for SDL_Delay()
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+SDL_InitDelay(void)
+{
+	int		i;
+	word	timer;
+
+	setvect(8,SDL_TimingService);		// Set to my timer 0 ISR
+
+	SDL_SetIntsPerSec(1000);			// Time 1ms
+
+	for (i = 0,timer = 0;i < 10;i++)	// Do timing test 10 times
+	{
+	asm	xor		dx,dx					// Zero DX
+	asm	mov		cx,0xffff				// Put starting value in CX
+	asm	mov		[TimerDone],cx			// TimerDone = false - 1
+startloop:
+	asm	or		[TimerDone],0
+	asm	jnz		startloop				// Make sure we're at the start
+loop:
+	asm	test	[TimerDone],1			// See if TimerDone flag got hit
+	asm	jnz		done					// Yep - drop out of the loop
+	asm	loop	loop
+done:
+
+		if (0xffff - TimerVal > timer)
+			timer = 0xffff - TimerVal;
+	}
+	timer += timer / 2;					// Use some slop
+	TimerDelay10 =  timer / (1000 / 10);
+	TimerDelay25 =  timer / (1000 / 25);
+	TimerDelay100 = timer / (1000 / 100);
+
+	SDL_SetTimer0(0);					// Reset timer 0
+
+	setvect(8,t0OldService);			// Set back to old ISR
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SDL_Delay() - Delays the specified amount of time
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+SDL_Delay(word delay)
+{
+	if (!delay)
+		return;
+
+asm	mov		cx,[delay]
+loop:
+asm	test	[TimerDone],0	// Useless code - just for timing equivilency
+asm	jnz		done
+asm	loop	loop
+done:;
+}
+#endif
+
+//
+//	PC Sound code
+//
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SDL_PCPlaySound() - Plays the specified sound on the PC speaker
+//
+///////////////////////////////////////////////////////////////////////////
+#ifdef	_MUSE_
+void
+#else
+static void
+#endif
+SDL_PCPlaySound(PCSound far *sound)
+{
+asm	pushf
+asm	cli
+
+	pcLastSample = -1;
+	pcLengthLeft = sound->common.length;
+	pcSound = sound->data;
+
+asm	popf
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SDL_PCStopSound() - Stops the current sound playing on the PC Speaker
+//
+///////////////////////////////////////////////////////////////////////////
+#ifdef	_MUSE_
+void
+#else
+static void
+#endif
+SDL_PCStopSound(void)
+{
+asm	pushf
+asm	cli
+
+	(long)pcSound = 0;
+
+asm	in	al,0x61		  	// Turn the speaker off
+asm	and	al,0xfd			// ~2
+asm	out	0x61,al
+
+asm	popf
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SDL_PCService() - Handles playing the next sample in a PC sound
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+SDL_PCService(void)
+{
+	byte	s;
+	word	t;
+
+	if (pcSound)
+	{
+		s = *pcSound++;
+		if (s != pcLastSample)
+		{
+		asm	pushf
+		asm	cli
+
+			pcLastSample = s;
+			if (s)					// We have a frequency!
+			{
+				t = pcSoundLookup[s];
+			asm	mov	bx,[t]
+
+			asm	mov	al,0xb6			// Write to channel 2 (speaker) timer
+			asm	out	43h,al
+			asm	mov	al,bl
+			asm	out	42h,al			// Low byte
+			asm	mov	al,bh
+			asm	out	42h,al			// High byte
+
+			asm	in	al,0x61			// Turn the speaker & gate on
+			asm	or	al,3
+			asm	out	0x61,al
+			}
+			else					// Time for some silence
+			{
+			asm	in	al,0x61		  	// Turn the speaker & gate off
+			asm	and	al,0xfc			// ~3
+			asm	out	0x61,al
+			}
+
+		asm	popf
+		}
+
+		if (!(--pcLengthLeft))
+		{
+			SDL_PCStopSound();
+			SDL_SoundFinished();
+		}
+	}
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SDL_ShutPC() - Turns off the pc speaker
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+SDL_ShutPC(void)
+{
+asm	pushf
+asm	cli
+
+	pcSound = 0;
+
+asm	in	al,0x61		  	// Turn the speaker & gate off
+asm	and	al,0xfc			// ~3
+asm	out	0x61,al
+
+asm	popf
+}
+
+// 	AdLib Code
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	alOut(n,b) - Puts b in AdLib card register n
+//
+///////////////////////////////////////////////////////////////////////////
+void
+alOut(byte n,byte b)
+{
+asm	pushf
+asm	cli
+
+asm	mov		dx,0x388
+asm	mov		al,[n]
+asm	out		dx,al
+#if 0
+	SDL_Delay(TimerDelay10);
+#else
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+#endif
+
+asm	mov		dx,0x389
+asm	mov		al,[b]
+asm	out		dx,al
+
+asm	popf
+
+#if 0
+	SDL_Delay(TimerDelay25);
+#else
+asm	mov	dx,0x388
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+asm	in	al, dx
+#endif
+}
+
+#if 0
+///////////////////////////////////////////////////////////////////////////
+//
+//	SDL_SetInstrument() - Puts an instrument into a generator
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+SDL_SetInstrument(int track,int which,Instrument far *inst,boolean percussive)
+{
+	byte		c,m;
+
+	if (percussive)
+	{
+		c = pcarriers[which];
+		m = pmodifiers[which];
+	}
+	else
+	{
+		c = carriers[which];
+		m = modifiers[which];
+	}
+
+	tracks[track - 1]->inst = *inst;
+	tracks[track - 1]->percussive = percussive;
+
+	alOut(m + alChar,inst->mChar);
+	alOut(m + alScale,inst->mScale);
+	alOut(m + alAttack,inst->mAttack);
+	alOut(m + alSus,inst->mSus);
+	alOut(m + alWave,inst->mWave);
+
+	// Most percussive instruments only use one cell
+	if (c != 0xff)
+	{
+		alOut(c + alChar,inst->cChar);
+		alOut(c + alScale,inst->cScale);
+		alOut(c + alAttack,inst->cAttack);
+		alOut(c + alSus,inst->cSus);
+		alOut(c + alWave,inst->cWave);
+	}
+
+	alOut(which + alFeedCon,inst->nConn);	// DEBUG - I think this is right
+}
+#endif
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SDL_ALStopSound() - Turns off any sound effects playing through the
+//		AdLib card
+//
+///////////////////////////////////////////////////////////////////////////
+#ifdef	_MUSE_
+void
+#else
+static void
+#endif
+SDL_ALStopSound(void)
+{
+asm	pushf
+asm	cli
+
+	(long)alSound = 0;
+	alOut(alFreqH + 0,0);
+
+asm	popf
+}
+
+static void
+SDL_AlSetFXInst(Instrument far *inst)
+{
+	byte		c,m;
+	byte		scale;	// added for "quiet AdLib" mode
+
+	m = modifiers[0];
+	c = carriers[0];
+	alOut(m + alChar,inst->mChar);
+	alOut(m + alScale,inst->mScale);
+	alOut(m + alAttack,inst->mAttack);
+	alOut(m + alSus,inst->mSus);
+	alOut(m + alWave,inst->mWave);
+	alOut(c + alChar,inst->cChar);
+#if 1
+	// quiet AdLib code:
+	scale = inst->cScale;
+	if (QuietFX)
+	{
+		scale = 0x3F-scale;
+		scale = (scale>>1) + (scale>>2);	// basically 'scale *= 0.75;'
+		scale = 0x3F-scale;
+	}
+	alOut(c + alScale,scale);
+#else
+	// old code:
+	alOut(c + alScale,inst->cScale);
+#endif
+	alOut(c + alAttack,inst->cAttack);
+	alOut(c + alSus,inst->cSus);
+	alOut(c + alWave,inst->cWave);
+	// DEBUG!!! - I just put this in
+//	alOut(alFeedCon,inst->nConn);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SDL_ALPlaySound() - Plays the specified sound on the AdLib card
+//
+///////////////////////////////////////////////////////////////////////////
+#ifdef	_MUSE_
+void
+#else
+static void
+#endif
+SDL_ALPlaySound(AdLibSound far *sound)
+{
+	Instrument	far *inst;
+
+	SDL_ALStopSound();
+
+asm	pushf
+asm	cli
+
+	alLengthLeft = sound->common.length;
+	alSound = sound->data;
+	alBlock = ((sound->block & 7) << 2) | 0x20;
+	inst = &sound->inst;
+
+	if (!(inst->mSus | inst->cSus))
+	{
+	asm	popf
+		Quit("SDL_ALPlaySound() - Bad instrument");
+	}
+
+	SDL_AlSetFXInst(inst);
+
+asm	popf
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+// 	SDL_ALSoundService() - Plays the next sample out through the AdLib card
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+SDL_ALSoundService(void)
+{
+	byte	s;
+
+	if (alSound)
+	{
+		s = *alSound++;
+		if (!s)
+			alOut(alFreqH + 0,0);
+		else
+		{
+			alOut(alFreqL + 0,s);
+			alOut(alFreqH + 0,alBlock);
+		}
+
+		if (!(--alLengthLeft))
+		{
+			(long)alSound = 0;
+			alOut(alFreqH + 0,0);
+			SDL_SoundFinished();
+		}
+	}
+}
+
+#if 0
+///////////////////////////////////////////////////////////////////////////
+//
+//	SDL_SelectMeasure() - sets up sequencing variables for a given track
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+SDL_SelectMeasure(ActiveTrack *track)
+{
+	track->seq = track->moods[track->mood];
+	track->nextevent = 0;
+}
+#endif
+
+static void
+SDL_ALService(void)
+{
+	byte	a,v;
+	word	w;
+
+	if (!sqActive)
+		return;
+
+	while (sqHackLen && (sqHackTime <= alTimeCount))
+	{
+		w = *sqHackPtr++;
+		sqHackTime = alTimeCount + *sqHackPtr++;
+	asm	mov	dx,[w]
+	asm	mov	[a],dl
+	asm	mov	[v],dh
+		alOut(a,v);
+		sqHackLen -= 4;
+	}
+	alTimeCount++;
+	if (!sqHackLen)
+	{
+		sqHackPtr = (word far *)sqHack;
+		sqHackLen = sqHackSeqLen;
+		alTimeCount = sqHackTime = 0;
+	}
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SDL_ShutAL() - Shuts down the AdLib card for sound effects
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+SDL_ShutAL(void)
+{
+asm	pushf
+asm	cli
+
+	alOut(alEffects,0);
+	alOut(alFreqH + 0,0);
+	SDL_AlSetFXInst(&alZeroInst);
+	alSound = 0;
+
+asm	popf
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SDL_CleanAL() - Totally shuts down the AdLib card
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+SDL_CleanAL(void)
+{
+	int	i;
+
+asm	pushf
+asm	cli
+
+	alOut(alEffects,0);
+	for (i = 1;i < 0xf5;i++)
+		alOut(i,0);
+
+asm	popf
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SDL_StartAL() - Starts up the AdLib card for sound effects
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+SDL_StartAL(void)
+{
+	alFXReg = 0;
+	alOut(alEffects,alFXReg);
+	SDL_AlSetFXInst(&alZeroInst);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SDL_DetectAdLib() - Determines if there's an AdLib (or SoundBlaster
+//		emulating an AdLib) present
+//
+///////////////////////////////////////////////////////////////////////////
+static boolean
+SDL_DetectAdLib(boolean force)
+{
+	byte	status1,status2;
+	int		i;
+
+	alOut(4,0x60);	// Reset T1 & T2
+	alOut(4,0x80);	// Reset IRQ
+	status1 = readstat();
+	alOut(2,0xff);	// Set timer 1
+	alOut(4,0x21);	// Start timer 1
+#if 0
+	SDL_Delay(TimerDelay100);
+#else
+	asm	mov	dx, 0x388;
+	asm	mov	cx, 100;
+waitloop:
+	asm	in 	al, dx;
+	asm	jmp	here;
+here:
+	asm	loop	waitloop;
+#endif
+
+	status2 = readstat();
+	alOut(4,0x60);
+	alOut(4,0x80);
+
+	if (force || (((status1 & 0xe0) == 0x00) && ((status2 & 0xe0) == 0xc0)))
+	{
+		for (i = 1;i <= 0xf5;i++)	// Zero all the registers
+			alOut(i,0);
+
+		alOut(1,0x20);	// Set WSE=1
+		alOut(8,0);		// Set CSM=0 & SEL=0
+
+		return(true);
+	}
+	else
+		return(false);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SDL_t0Service() - My timer 0 ISR which handles the different timings and
+//		dispatches to whatever other routines are appropriate
+//
+///////////////////////////////////////////////////////////////////////////
+static void interrupt
+SDL_t0Service(void)
+{
+static	word	count = 1;
+
+#if 0	// for debugging
+asm	mov	dx,STATUS_REGISTER_1
+asm	in	al,dx
+asm	mov	dx,ATR_INDEX
+asm	mov	al,ATR_OVERSCAN
+asm	out	dx,al
+asm	mov	al,4	// red
+asm	out	dx,al
+#endif
+
+	HackCount++;
+
+	if (MusicMode == smm_AdLib)
+	{
+		SDL_ALService();
+		if (!(++count & 7))
+		{
+			LocalTime++;
+			TimeCount++;
+			if (SoundUserHook)
+				SoundUserHook();
+		}
+		if (!(count & 3))
+		{
+			switch (SoundMode)
+			{
+			case sdm_PC:
+				SDL_PCService();
+				break;
+			case sdm_AdLib:
+				SDL_ALSoundService();
+				break;
+			}
+		}
+	}
+	else
+	{
+		if (!(++count & 1))
+		{
+			LocalTime++;
+			TimeCount++;
+			if (SoundUserHook)
+				SoundUserHook();
+		}
+		switch (SoundMode)
+		{
+		case sdm_PC:
+			SDL_PCService();
+			break;
+		case sdm_AdLib:
+			SDL_ALSoundService();
+			break;
+		}
+	}
+
+asm	mov	ax,[WORD PTR TimerCount]
+asm	add	ax,[WORD PTR TimerDivisor]
+asm	mov	[WORD PTR TimerCount],ax
+asm	jnc	myack
+	t0OldService();			// If we overflow a word, time to call old int handler
+asm	jmp	olddone
+myack:;
+	outportb(0x20,0x20);	// Ack the interrupt
+olddone:;
+
+#if 0	// for debugging
+asm	mov	dx,STATUS_REGISTER_1
+asm	in	al,dx
+asm	mov	dx,ATR_INDEX
+asm	mov	al,ATR_OVERSCAN
+asm	out	dx,al
+asm	mov	al,3	// blue
+asm	out	dx,al
+asm	mov	al,0x20	// normal
+asm	out	dx,al
+#endif
+}
+
+////////////////////////////////////////////////////////////////////////////
+//
+//	SDL_ShutDevice() - turns off whatever device was being used for sound fx
+//
+////////////////////////////////////////////////////////////////////////////
+static void
+SDL_ShutDevice(void)
+{
+	switch (SoundMode)
+	{
+	case sdm_PC:
+		SDL_ShutPC();
+		break;
+	case sdm_AdLib:
+		SDL_ShutAL();
+		break;
+	}
+	SoundMode = sdm_Off;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SDL_CleanDevice() - totally shuts down all sound devices
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+SDL_CleanDevice(void)
+{
+	if ((SoundMode == sdm_AdLib) || (MusicMode == smm_AdLib))
+		SDL_CleanAL();
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SDL_StartDevice() - turns on whatever device is to be used for sound fx
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+SDL_StartDevice(void)
+{
+	switch (SoundMode)
+	{
+	case sdm_AdLib:
+		SDL_StartAL();
+		break;
+	}
+	SoundNumber = SoundPriority = 0;
+}
+
+static void
+SDL_SetTimerSpeed(void)
+{
+	word	rate;
+
+	if (MusicMode == smm_AdLib)
+		rate = TickBase * 8;
+	else
+		rate = TickBase * 2;
+	SDL_SetIntsPerSec(rate);
+}
+
+//	Public routines
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SD_SetSoundMode() - Sets which sound hardware to use for sound effects
+//
+///////////////////////////////////////////////////////////////////////////
+boolean
+SD_SetSoundMode(SDMode mode)
+{
+	boolean	result;
+	word	tableoffset;
+
+	SD_StopSound();
+
+#ifndef	_MUSE_
+	switch (mode)
+	{
+	case sdm_Off:
+		NeedsDigitized = false;
+		result = true;
+		break;
+	case sdm_PC:
+		tableoffset = STARTPCSOUNDS;
+		NeedsDigitized = false;
+		result = true;
+		break;
+	case sdm_AdLib:
+		if (AdLibPresent)
+		{
+			tableoffset = STARTADLIBSOUNDS;
+			NeedsDigitized = false;
+			result = true;
+		}
+		break;
+	default:
+		result = false;
+		break;
+	}
+#endif
+
+	if (result && (mode != SoundMode))
+	{
+		SDL_ShutDevice();
+		SoundMode = mode;
+#ifndef	_MUSE_
+		SoundTable = (word *)(&audiosegs[tableoffset]);
+#endif
+		SDL_StartDevice();
+	}
+
+	SDL_SetTimerSpeed();
+
+	return(result);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SD_SetMusicMode() - sets the device to use for background music
+//
+///////////////////////////////////////////////////////////////////////////
+boolean
+SD_SetMusicMode(SMMode mode)
+{
+	boolean	result;
+
+	SD_FadeOutMusic();
+	while (SD_MusicPlaying())
+		;
+
+	switch (mode)
+	{
+	case smm_Off:
+		NeedsMusic = false;
+		result = true;
+		break;
+	case smm_AdLib:
+		if (AdLibPresent)
+		{
+			NeedsMusic = true;
+			result = true;
+		}
+		break;
+	default:
+		result = false;
+		break;
+	}
+
+	if (result)
+		MusicMode = mode;
+
+	SDL_SetTimerSpeed();
+
+	return(result);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SD_Startup() - starts up the Sound Mgr
+//		Detects all additional sound hardware and installs my ISR
+//
+///////////////////////////////////////////////////////////////////////////
+void
+SD_Startup(void)
+{
+	int	i;
+	boolean alForce;
+
+	alForce = false;
+
+	if (SD_Started)
+		return;
+
+	ssIsTandy = false;
+	alNoCheck = false;
+#ifndef	_MUSE_
+	for (i = 1;i < _argc;i++)
+	{
+		switch (US_CheckParm(_argv[i],ParmStrings))
+		{
+		case 0:						// No AdLib detection
+			alNoCheck = true;
+			break;
+
+		case 1:
+			alForce = true;
+			break;
+		}
+	}
+#endif
+
+	SoundUserHook = 0;
+
+	t0OldService = getvect(8);	// Get old timer 0 ISR
+
+	//SDL_InitDelay();			// SDL_InitDelay() uses t0OldService
+
+	setvect(8,SDL_t0Service);	// Set to my timer 0 ISR
+	LocalTime = TimeCount = alTimeCount = 0;
+
+	SD_SetSoundMode(sdm_Off);
+	SD_SetMusicMode(smm_Off);
+
+	if (!alNoCheck)
+		AdLibPresent = SDL_DetectAdLib(alForce);
+
+	for (i = 0;i < 255;i++)
+		pcSoundLookup[i] = i * 60;
+
+	SD_Started = true;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SD_Default() - Sets up the default behaviour for the Sound Mgr whether
+//		the config file was present or not.
+//
+///////////////////////////////////////////////////////////////////////////
+void
+SD_Default(boolean gotit,SDMode sd,SMMode sm)
+{
+	boolean	gotsd,gotsm;
+
+	gotsd = gotsm = gotit;
+
+	if (gotsd)	// Make sure requested sound hardware is available
+	{
+		switch (sd)
+		{
+		case sdm_AdLib:
+			gotsd = AdLibPresent;
+			break;
+		}
+	}
+	if (!gotsd)
+	{
+		if (AdLibPresent)
+			sd = sdm_AdLib;
+		else
+			sd = sdm_PC;
+	}
+	if (sd != SoundMode)
+		SD_SetSoundMode(sd);
+
+
+	if (gotsm)	// Make sure requested music hardware is available
+	{
+		switch (sm)
+		{
+		case sdm_AdLib:		// BUG: this should use smm_AdLib!
+			gotsm = AdLibPresent;
+			break;
+		}
+	}
+	if (!gotsm)
+	{
+		if (AdLibPresent)
+			sm = smm_AdLib;
+		else
+			sm = smm_Off;
+	}
+	if (sm != MusicMode)
+		SD_SetMusicMode(sm);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SD_Shutdown() - shuts down the Sound Mgr
+//		Removes sound ISR and turns off whatever sound hardware was active
+//
+///////////////////////////////////////////////////////////////////////////
+void
+SD_Shutdown(void)
+{
+	if (!SD_Started)
+		return;
+
+	SD_MusicOff();
+	SDL_ShutDevice();
+	SDL_CleanDevice();
+
+	asm	pushf
+	asm	cli
+
+	SDL_SetTimer0(0);
+
+	setvect(8,t0OldService);
+
+	asm	popf
+
+	SD_Started = false;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SD_SetUserHook() - sets the routine that the Sound Mgr calls every 1/70th
+//		of a second from its timer 0 ISR
+//
+///////////////////////////////////////////////////////////////////////////
+void
+SD_SetUserHook(void (* hook)(void))
+{
+	// BUG: interrupts should be disabled while setting SoundUserHook!
+	SoundUserHook = hook;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SD_PlaySound() - plays the specified sound on the appropriate hardware
+//
+///////////////////////////////////////////////////////////////////////////
+void
+SD_PlaySound(soundnames sound)
+{
+	SoundCommon	far *s;
+
+	if ((SoundMode == sdm_Off) /*|| (sound == -1)*/)
+		return;
+
+	s = MK_FP(SoundTable[sound],0);
+	if (!s)
+		Quit("SD_PlaySound() - Uncached sound");
+	if (!s->length)
+		Quit("SD_PlaySound() - Zero length sound");
+	if (s->priority < SoundPriority)
+		return;
+
+	switch (SoundMode)
+	{
+	case sdm_PC:
+		SDL_PCPlaySound((void far *)s);
+		break;
+	case sdm_AdLib:
+		SDL_ALPlaySound((void far *)s);
+		break;
+	}
+
+	SoundNumber = sound;
+	SoundPriority = s->priority;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SD_SoundPlaying() - returns the sound number that's playing, or 0 if
+//		no sound is playing
+//
+///////////////////////////////////////////////////////////////////////////
+word
+SD_SoundPlaying(void)
+{
+	boolean	result = false;
+
+	switch (SoundMode)
+	{
+	case sdm_PC:
+		result = pcSound? true : false;
+		break;
+	case sdm_AdLib:
+		result = alSound? true : false;
+		break;
+	}
+
+	if (result)
+		return(SoundNumber);
+	else
+		return(false);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SD_StopSound() - if a sound is playing, stops it
+//
+///////////////////////////////////////////////////////////////////////////
+void
+SD_StopSound(void)
+{
+	switch (SoundMode)
+	{
+	case sdm_PC:
+		SDL_PCStopSound();
+		break;
+	case sdm_AdLib:
+		SDL_ALStopSound();
+		break;
+	}
+
+	SDL_SoundFinished();
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SD_WaitSoundDone() - waits until the current sound is done playing
+//
+///////////////////////////////////////////////////////////////////////////
+void
+SD_WaitSoundDone(void)
+{
+	while (SD_SoundPlaying())
+		;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SD_MusicOn() - turns on the sequencer
+//
+///////////////////////////////////////////////////////////////////////////
+void
+SD_MusicOn(void)
+{
+	sqActive = true;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SD_MusicOff() - turns off the sequencer and any playing notes
+//
+///////////////////////////////////////////////////////////////////////////
+void
+SD_MusicOff(void)
+{
+	word	i;
+
+
+	switch (MusicMode)
+	{
+	case smm_AdLib:
+		alFXReg = 0;
+		alOut(alEffects,0);
+		for (i = 0;i < sqMaxTracks;i++)
+			alOut(alFreqH + i + 1,0);
+		break;
+	}
+	sqActive = false;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SD_StartMusic() - starts playing the music pointed to
+//
+///////////////////////////////////////////////////////////////////////////
+void
+SD_StartMusic(MusicGroup far *music)
+{
+	SD_MusicOff();
+asm	pushf
+asm	cli
+
+	if (MusicMode == smm_AdLib)
+	{
+		sqHackPtr = sqHack = music->values;
+		sqHackSeqLen = sqHackLen = music->length;
+		sqHackTime = 0;
+		alTimeCount = 0;
+		SD_MusicOn();
+	}
+
+asm	popf
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SD_FadeOutMusic() - starts fading out the music. Call SD_MusicPlaying()
+//		to see if the fadeout is complete
+//
+///////////////////////////////////////////////////////////////////////////
+void
+SD_FadeOutMusic(void)
+{
+	switch (MusicMode)
+	{
+	case smm_AdLib:
+		// DEBUG - quick hack to turn the music off
+		SD_MusicOff();
+		break;
+	}
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//	SD_MusicPlaying() - returns true if music is currently playing, false if
+//		not
+//
+///////////////////////////////////////////////////////////////////////////
+boolean
+SD_MusicPlaying(void)
+{
+	boolean	result;
+
+	switch (MusicMode)
+	{
+	case smm_AdLib:
+		result = false;
+		// DEBUG - not written
+		break;
+	default:
+		result = false;
+	}
+
+	return(result);
+}
diff --git a/16/keen456/KEEN4-6/ID_SD.H b/16/keen456/KEEN4-6/ID_SD.H
new file mode 100755
index 00000000..a48e442a
--- /dev/null
+++ b/16/keen456/KEEN4-6/ID_SD.H
@@ -0,0 +1,210 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+//
+//	ID Engine
+//	ID_SD.h - Sound Manager Header
+//	v1.0d1
+//	By Jason Blochowiak
+//
+
+#ifndef	__TYPES__
+#include "ID_Types.h"
+#endif
+
+#ifndef	__ID_SD__
+#define	__ID_SD__
+
+#ifdef	__DEBUG__
+#define	__DEBUG_SoundMgr__
+#endif
+
+#define	TickBase	70		// 70Hz per tick - used as a base for timer 0
+
+typedef	enum	{
+					sdm_Off,
+					sdm_PC,sdm_AdLib,
+				}	SDMode;
+typedef	enum	{
+					smm_Off,smm_AdLib
+				}	SMMode;
+
+typedef	struct
+		{
+			longword	length;
+			word		priority;
+		} SoundCommon;
+
+//	PC Sound stuff
+#define	pcTimer		0x42
+#define	pcTAccess	0x43
+#define	pcSpeaker	0x61
+
+#define	pcSpkBits	3
+
+typedef	struct
+		{
+			SoundCommon	common;
+			byte		data[1];
+		} PCSound;
+
+// 	Registers for the Sound Blaster card - needs to be offset by n0
+#define	sbReset		0x206
+#define	sbReadData	0x20a
+#define	sbWriteCmd	0x20c
+#define	sbWriteData	0x20c
+#define	sbWriteStat	0x20c
+#define	sbDataAvail	0x20e
+
+typedef	struct
+		{
+			SoundCommon	common;
+			word		hertz;
+			byte		bits,
+						reference,
+						data[1];
+		} SampledSound;
+
+// 	Registers for the AdLib card
+// Operator stuff
+#define	alChar		0x20
+#define	alScale		0x40
+#define	alAttack	0x60
+#define	alSus		0x80
+#define	alWave		0xe0
+// Channel stuff
+#define	alFreqL		0xa0
+#define	alFreqH		0xb0
+#define	alFeedCon	0xc0
+// Global stuff
+#define	alEffects	0xbd
+
+typedef	struct
+		{
+			byte	mChar,cChar,
+					mScale,cScale,
+					mAttack,cAttack,
+					mSus,cSus,
+					mWave,cWave,
+					nConn,
+
+					// These are only for Muse - these bytes are really unused
+					voice,
+					mode,
+					unused[3];
+		} Instrument;
+
+typedef	struct
+		{
+			SoundCommon	common;
+			Instrument	inst;
+			byte		block,
+						data[1];
+		} AdLibSound;
+
+//
+//	Sequencing stuff
+//
+#define	sqMaxTracks	10
+#define	sqMaxMoods	1	// DEBUG
+
+#define	sev_Null		0	// Does nothing
+#define	sev_NoteOff		1	// Turns a note off
+#define	sev_NoteOn		2	// Turns a note on
+#define	sev_NotePitch	3	// Sets the pitch of a currently playing note
+#define	sev_NewInst		4	// Installs a new instrument
+#define	sev_NewPerc		5	// Installs a new percussive instrument
+#define	sev_PercOn		6	// Turns a percussive note on
+#define	sev_PercOff		7	// Turns a percussive note off
+#define	sev_SeqEnd		-1	// Terminates a sequence
+
+// 	Flags for MusicGroup.flags
+#define	sf_Melodic		0
+#define	sf_Percussive	1
+
+#if 1
+typedef	struct
+		{
+			word	length,
+					values[1];
+		} MusicGroup;
+#else
+typedef	struct
+		{
+			word	flags,
+					count,
+					offsets[1];
+		} MusicGroup;
+#endif
+
+typedef	struct
+		{
+			/* This part needs to be set up by the user */
+			word        mood,far *moods[sqMaxMoods];
+
+			/* The rest is set up by the code */
+			Instrument	inst;
+			boolean		percussive;
+			word		far *seq;
+			longword	nextevent;
+		} ActiveTrack;
+
+#define	sqmode_Normal		0
+#define	sqmode_FadeIn		1
+#define	sqmode_FadeOut		2
+
+#define	sqMaxFade		64	// DEBUG
+
+
+// Global variables
+extern	boolean		AdLibPresent,
+					NeedsMusic,	// For Caching Mgr
+					QuietFX;
+extern	SDMode		SoundMode;
+extern	SMMode		MusicMode;
+extern	longword	TimeCount;					// Global time in ticks
+
+// Function prototypes
+extern	void	SD_Startup(void),
+				SD_Shutdown(void),
+				SD_Default(boolean gotit,SDMode sd,SMMode sm),
+				SD_PlaySound(soundnames sound),
+				SD_StopSound(void),
+				SD_WaitSoundDone(void),
+				SD_StartMusic(MusicGroup far *music),
+				SD_MusicOn(void),
+				SD_MusicOff(void),
+				SD_FadeOutMusic(void),
+				SD_SetUserHook(void (*hook)(void));
+extern	boolean	SD_MusicPlaying(void),
+				SD_SetSoundMode(SDMode mode),
+				SD_SetMusicMode(SMMode mode);
+extern	word	SD_SoundPlaying(void);
+
+#ifdef	_MUSE_	// MUSE Goes directly to the lower level routines
+extern	void	SDL_PCPlaySound(PCSound far *sound),
+				SDL_PCStopSound(void),
+				SDL_ALPlaySound(AdLibSound far *sound),
+				SDL_ALStopSound(void);
+#endif
+
+#endif
diff --git a/16/keen456/KEEN4-6/ID_US.H b/16/keen456/KEEN4-6/ID_US.H
new file mode 100755
index 00000000..2e50d2a7
--- /dev/null
+++ b/16/keen456/KEEN4-6/ID_US.H
@@ -0,0 +1,160 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+//
+//	ID Engine
+//	ID_US.h - Header file for the User Manager
+//	v1.0d1
+//	By Jason Blochowiak
+//
+
+#ifndef	__TYPES__
+#include "ID_Types.h"
+#endif
+
+#ifndef	__ID_US__
+#define	__ID_US__
+
+#ifdef	__DEBUG__
+#define	__DEBUG_UserMgr__
+#endif
+
+//#define	HELPTEXTLINKED
+
+#define	MaxX	320
+#define	MaxY	200
+
+#define	MaxHelpLines	500
+
+#define	MaxHighName	57
+#ifdef CAT3D
+#define	MaxScores	7
+#else
+#define	MaxScores	8
+#endif
+typedef	struct
+		{
+			char	name[MaxHighName + 1];
+			long	score;
+			word	completed;
+		} HighScore;
+
+#define	MaxGameName		32
+#define	MaxSaveGames	6
+typedef	struct
+		{
+			char	signature[4];
+			word	*oldtest;
+			boolean	present;
+			char	name[MaxGameName + 1];
+		} SaveGame;
+
+#define	MaxString	128	// Maximum input string size
+
+typedef	struct
+		{
+			int	x,y,
+				w,h,
+				px,py;
+		} WindowRec;	// Record used to save & restore screen windows
+
+typedef	enum
+		{
+			gd_Continue,
+			gd_Easy,
+			gd_Normal,
+			gd_Hard
+		} GameDiff;
+
+//	Hack import for TED launch support
+extern	boolean		tedlevel;
+extern	word		tedlevelnum;
+extern	void		TEDDeath(void);
+
+extern	boolean		ingame,		// Set by game code if a game is in progress
+					abortgame,	// Set if a game load failed
+					loadedgame,	// Set if the current game was loaded
+#ifdef KEEN6
+					checkpassed,
+#endif
+					NoWait,
+					HighScoresDirty;
+extern	char		*abortprogram;	// Set to error msg if program is dying
+extern	GameDiff	restartgame;	// Normally gd_Continue, else starts game
+extern	word		PrintX,PrintY;	// Current printing location in the window
+extern	word		WindowX,WindowY,// Current location of window
+					WindowW,WindowH;// Current size of window
+
+extern	boolean		Button0,Button1,
+					CursorBad;
+extern	int			CursorX,CursorY;
+
+extern	void		(*USL_MeasureString)(char far *,word *,word *),
+					(*USL_DrawString)(char far *);
+
+extern	boolean		(*USL_SaveGame)(int),(*USL_LoadGame)(int);
+extern	void		(*USL_ResetGame)(void);
+extern	SaveGame	Games[MaxSaveGames];
+extern	HighScore	Scores[];
+
+#define	US_HomeWindow()	{PrintX = WindowX; PrintY = WindowY;}
+
+extern	void	US_Startup(void),
+				US_Setup(void),
+				US_Shutdown(void),
+				US_InitRndT(boolean randomize),
+				US_SetLoadSaveHooks(boolean (*load)(int),
+									boolean (*save)(int),
+									void (*reset)(void)),
+				US_TextScreen(void),
+				US_UpdateTextScreen(void),
+				US_FinishTextScreen(void),
+				US_ControlPanel(void),
+				US_DrawWindow(word x,word y,word w,word h),
+				US_CenterWindow(word,word),
+				US_SaveWindow(WindowRec *win),
+				US_RestoreWindow(WindowRec *win),
+				US_ClearWindow(void),
+				US_SetPrintRoutines(void (*measure)(char far *,word *,word *),
+									void (*print)(char far *)),
+				US_PrintCentered(char *s),
+				US_CPrint(char *s),
+				US_CPrintLine(char *s),
+				US_Print(char *s),
+				US_PrintUnsigned(longword n),
+				US_PrintSigned(long n),
+				US_StartCursor(void),
+				US_ShutCursor(void),
+				US_ControlPanel(void),
+				US_CheckHighScore(long score,word other),
+				US_DisplayHighScores(int which);
+extern	boolean	US_UpdateCursor(void),
+				US_LineInput(int x,int y,char *buf,char *def,boolean escok,
+								int maxchars,int maxwidth);
+extern	int		US_CheckParm(char *parm,char **strings),
+				US_RndT(void);
+
+extern	boolean US_ParmPresent(char *arg);
+
+		void	USL_PrintInCenter(char *s,Rect r);
+		char 	*USL_GiveSaveName(word game);
+#endif
diff --git a/16/keen456/KEEN4-6/ID_US_1.C b/16/keen456/KEEN4-6/ID_US_1.C
new file mode 100755
index 00000000..d7b27aac
--- /dev/null
+++ b/16/keen456/KEEN4-6/ID_US_1.C
@@ -0,0 +1,1358 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+//
+//      ID Engine
+//      ID_US_1.c - User Manager - General routines
+//      v1.1d1
+//      By Jason Blochowiak
+//      Hacked up for Catacomb 3D
+//
+
+//
+//      This module handles dealing with user input & feedback
+//
+//      Depends on: Input Mgr, View Mgr, some variables from the Sound, Caching,
+//              and Refresh Mgrs, Memory Mgr for background save/restore
+//
+//      Globals:
+//              ingame - Flag set by game indicating if a game is in progress
+//      abortgame - Flag set if the current game should be aborted (if a load
+//                      game fails)
+//              loadedgame - Flag set if a game was loaded
+//              abortprogram - Normally nil, this points to a terminal error message
+//                      if the program needs to abort
+//              restartgame - Normally set to gd_Continue, this is set to one of the
+//                      difficulty levels if a new game should be started
+//              PrintX, PrintY - Where the User Mgr will print (global coords)
+//              WindowX,WindowY,WindowW,WindowH - The dimensions of the current
+//                      window
+//
+
+#include "ID_HEADS.H"
+
+#pragma hdrstop
+
+#pragma warn    -pia
+
+
+//      Special imports
+extern  boolean         showscorebox;
+#ifdef  KEEN
+extern	boolean		jerk;
+extern  boolean         oldshooting;
+extern  ScanCode        firescan;
+#else
+		ScanCode        firescan;
+#endif
+
+//      Global variables
+		char            *abortprogram;
+		boolean         NoWait,
+					HighScoresDirty;
+		word            PrintX,PrintY;
+		word            WindowX,WindowY,WindowW,WindowH;
+
+//      Internal variables
+#define ConfigVersion   4
+
+static  char            *ParmStrings[] = {"TEDLEVEL","NOWAIT"},
+					*ParmStrings2[] = {"COMP","NOCOMP"};
+static  boolean         US_Started;
+
+		boolean         Button0,Button1,
+					CursorBad;
+		int                     CursorX,CursorY;
+
+		void            (*USL_MeasureString)(char far *,word *,word *) = VW_MeasurePropString,
+					(*USL_DrawString)(char far *) = VWB_DrawPropString;
+
+		boolean         (*USL_SaveGame)(int),(*USL_LoadGame)(int);
+		void            (*USL_ResetGame)(void);
+		SaveGame        Games[MaxSaveGames];
+		HighScore       Scores[MaxScores] =
+					{
+#if defined CAT3D
+						{"Sir Lancelot",500,3},
+						{"",0},
+						{"",0},
+						{"",0},
+						{"",0},
+						{"",0},
+						{"",0},
+#elif defined GOODTIMES
+						{"Id Software",10000,0},
+						{"Adrian Carmack",10000,0},
+						{"John Carmack",10000,0},
+						{"Kevin Cloud",10000,0},
+						{"Shawn Green",10000,0},
+						{"Tom Hall",10000,0},
+						{"John Romero",10000,0},
+						{"Jay Wilbur",10000,0},
+#else
+						{"Id Software - '91",10000,0},
+						{"",10000,0},
+						{"Jason Blochowiak",10000,0},
+						{"Adrian Carmack",10000,0},
+						{"John Carmack",10000,0},
+						{"Tom Hall",10000,0},
+						{"John Romero",10000,0},
+						{"",10000,0},
+#endif
+					};
+
+//      Internal routines
+
+//      Public routines
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      USL_HardError() - Handles the Abort/Retry/Fail sort of errors passed
+//                      from DOS.
+//
+///////////////////////////////////////////////////////////////////////////
+#pragma warn    -par
+#pragma warn    -rch
+int
+USL_HardError(word errval,int ax,int bp,int si)
+{
+#define IGNORE  0
+#define RETRY   1
+#define ABORT   2
+extern  void    ShutdownId(void);
+
+static  char            buf[32];
+static  WindowRec       wr;
+		int                     di;
+		char            c,*s,*t;
+
+
+	di = _DI;
+
+	if (ax < 0)
+		s = "Device Error";
+	else
+	{
+		if ((di & 0x00ff) == 0)
+			s = "Drive ~ is Write Protected";
+		else
+			s = "Error on Drive ~";
+		for (t = buf;*s;s++,t++)        // Can't use sprintf()
+			if ((*t = *s) == '~')
+				*t = (ax & 0x00ff) + 'A';
+		*t = '\0';
+		s = buf;
+	}
+
+	c = peekb(0x40,0x49);   // Get the current screen mode
+	if ((c < 4) || (c == 7))
+		goto oh_kill_me;
+
+	// DEBUG - handle screen cleanup
+
+	US_SaveWindow(&wr);
+	US_CenterWindow(30,3);
+	US_CPrint(s);
+	US_CPrint("(R)etry or (A)bort?");
+	VW_UpdateScreen();
+	IN_ClearKeysDown();
+
+asm     sti     // Let the keyboard interrupts come through
+
+	while (true)
+	{
+		switch (IN_WaitForASCII())
+		{
+		case key_Escape:
+		case 'a':
+		case 'A':
+			goto oh_kill_me;
+			break;
+		case key_Return:
+		case key_Space:
+		case 'r':
+		case 'R':
+			US_ClearWindow();
+			VW_UpdateScreen();
+			US_RestoreWindow(&wr);
+			return(RETRY);
+			break;
+		}
+	}
+
+oh_kill_me:
+	abortprogram = s;
+	ShutdownId();
+	fprintf(stderr,"Terminal Error: %s\n",s);
+	if (tedlevel)
+		fprintf(stderr,"You launched from TED. I suggest that you reboot...\n");
+
+	return(ABORT);
+#undef  IGNORE
+#undef  RETRY
+#undef  ABORT
+}
+#pragma warn    +par
+#pragma warn    +rch
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      USL_GiveSaveName() - Returns a pointer to a static buffer that contains
+//              the filename to use for the specified save game
+//
+///////////////////////////////////////////////////////////////////////////
+char *
+USL_GiveSaveName(word game)
+{
+static  char    name[] = "SAVEGAMx."EXTENSION;
+
+	name[7] = '0' + game;
+	return(name);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_SetLoadSaveHooks() - Sets the routines that the User Mgr calls after
+//              reading or writing the save game headers
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_SetLoadSaveHooks(boolean (*load)(int),boolean (*save)(int),void (*reset)(void))
+{
+	USL_LoadGame = load;
+	USL_SaveGame = save;
+	USL_ResetGame = reset;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      USL_ReadConfig() - Reads the configuration file, if present, and sets
+//              things up accordingly. If it's not present, uses defaults. This file
+//              includes the high scores.
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+USL_ReadConfig(void)
+{
+	boolean         gotit, hadAdLib;
+	char            sig[sizeof(EXTENSION)];
+	word            version;
+	int                     file;
+	SDMode          sd;
+	SMMode          sm;
+	ControlType     ctl;
+
+	if ((file = open("CONFIG."EXTENSION,O_BINARY | O_RDONLY)) != -1)
+	{
+		read(file,sig,sizeof(EXTENSION));
+		read(file,&version,sizeof(version));
+		if (strcmp(sig,EXTENSION) || (version != ConfigVersion))
+		{
+			close(file);
+			goto rcfailed;
+		}
+		read(file,Scores,sizeof(HighScore) * MaxScores);
+		read(file,&sd,sizeof(sd));
+		read(file,&sm,sizeof(sm));
+		read(file,&ctl,sizeof(ctl));
+		read(file,&(KbdDefs[0]),sizeof(KbdDefs[0]));
+		read(file,&showscorebox,sizeof(showscorebox));
+		read(file,&compatability,sizeof(compatability));
+		read(file,&QuietFX,sizeof(QuietFX));
+		read(file,&hadAdLib,sizeof(hadAdLib));
+		read(file,&jerk,sizeof(jerk));
+#ifdef KEEN
+		read(file,&oldshooting,sizeof(oldshooting));
+		read(file,&firescan,sizeof(firescan));
+#endif
+		read(file,&GravisGamepad,sizeof(GravisGamepad));
+		read(file,&GravisMap,sizeof(GravisMap));
+		close(file);
+
+		HighScoresDirty = false;
+		gotit = true;
+	}
+	else
+	{
+rcfailed:
+		sd = sdm_Off;
+		sm = smm_Off;
+		ctl = ctrl_Keyboard;
+		showscorebox = true;
+#ifdef KEEN
+		oldshooting = false;
+#endif
+
+		gotit = false;
+		HighScoresDirty = true;
+	}
+
+	SD_Default(gotit? (hadAdLib==AdLibPresent) : false, sd,sm);
+	IN_Default(gotit,ctl);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      USL_WriteConfig() - Writes out the current configuration, including the
+//              high scores.
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+USL_WriteConfig(void)
+{
+	word    version;
+	int             file;
+
+	version = ConfigVersion;
+	file = open("CONFIG."EXTENSION,O_CREAT | O_BINARY | O_WRONLY,
+				S_IREAD | S_IWRITE | S_IFREG);
+	if (file != -1)
+	{
+		write(file,EXTENSION,sizeof(EXTENSION));
+		write(file,&version,sizeof(version));
+		write(file,Scores,sizeof(HighScore) * MaxScores);
+		write(file,&SoundMode,sizeof(SoundMode));
+		write(file,&MusicMode,sizeof(MusicMode));
+#ifdef CAT3D
+		if      // Hack
+		(
+			(Controls[0] == ctrl_Joystick1)
+		||      (Controls[0] == ctrl_Joystick2)
+		)
+			Controls[0] = ctrl_Keyboard;
+#endif
+		write(file,&(Controls[0]),sizeof(Controls[0]));
+		write(file,&(KbdDefs[0]),sizeof(KbdDefs[0]));
+		write(file,&showscorebox,sizeof(showscorebox));
+		write(file,&compatability,sizeof(compatability));
+		write(file,&QuietFX,sizeof(QuietFX));
+		write(file,&AdLibPresent,sizeof(AdLibPresent));
+		write(file,&jerk,sizeof(jerk));
+#ifdef KEEN
+		write(file,&oldshooting,sizeof(oldshooting));
+		write(file,&firescan,sizeof(firescan));
+#endif
+		write(file,&GravisGamepad,sizeof(GravisGamepad));
+		write(file,&GravisMap,sizeof(GravisMap));
+		close(file);
+	}
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      USL_CheckSavedGames() - Checks to see which saved games are present
+//              & valid
+//
+///////////////////////////////////////////////////////////////////////////
+#ifdef KEEN
+void
+#else
+static void
+#endif
+USL_CheckSavedGames(void)
+{
+	boolean         ok;
+	char            *filename;
+	word            i;
+	int                     file;
+	SaveGame        *game;
+
+#ifdef CAT3D
+	USL_SaveGame = 0;
+	USL_LoadGame = 0;
+#endif
+
+	for (i = 0,game = Games;i < MaxSaveGames;i++,game++)
+	{
+		filename = USL_GiveSaveName(i);
+		ok = false;
+		if ((file = open(filename,O_BINARY | O_RDONLY)) != -1)
+		{
+			if
+			(
+				(read(file,game,sizeof(*game)) == sizeof(*game))
+			&&      (!strcmp(game->signature,EXTENSION))
+			&&      (game->oldtest == &PrintX)
+			)
+				ok = true;
+
+			close(file);
+		}
+
+		if (ok)
+			game->present = true;
+		else
+		{
+			strcpy(game->signature,EXTENSION);
+			game->present = false;
+			strcpy(game->name,"Empty");
+		}
+	}
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_Startup() - Starts the User Mgr
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_Startup(void)
+{
+	int     i;
+
+	if (US_Started)
+		return;
+
+	harderr(USL_HardError); // Install the fatal error handler
+
+	US_InitRndT(true);              // Initialize the random number generator
+
+	USL_ReadConfig();               // Read config file
+
+	for (i = 1;i < _argc;i++)
+	{
+		switch (US_CheckParm(_argv[i],ParmStrings2))
+		{
+		case 0:
+			if (grmode == EGAGR)
+				compatability = true;
+			break;
+		case 1:
+			compatability = false;
+			break;
+		}
+	}
+
+	US_Started = true;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_Setup() - Does the disk access part of the User Mgr's startup
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_Setup(void)
+{
+#ifndef CAT3D
+	USL_SaveGame = 0;
+	USL_LoadGame = 0;
+#endif
+	USL_CheckSavedGames();  // Check which saved games are present
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_Shutdown() - Shuts down the User Mgr
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_Shutdown(void)
+{
+	if (!US_Started)
+		return;
+
+	if (!abortprogram)
+		USL_WriteConfig();
+
+	US_Started = false;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_CheckParm() - checks to see if a string matches one of a set of
+//              strings. The check is case insensitive. The routine returns the
+//              index of the string that matched, or -1 if no matches were found
+//
+///////////////////////////////////////////////////////////////////////////
+int
+US_CheckParm(char *parm,char **strings)
+{
+	char    cp,cs,
+			*p,*s;
+	int             i;
+
+	while (!isalpha(*parm)) // Skip non-alphas
+		parm++;
+
+	for (i = 0;*strings && **strings;i++)
+	{
+		for (s = *strings++,p = parm,cs = cp = 0;cs == cp;)
+		{
+			cs = *s++;
+			if (!cs)
+				return(i);
+			cp = *p++;
+
+			if (isupper(cs))
+				cs = tolower(cs);
+			if (isupper(cp))
+				cp = tolower(cp);
+		}
+	}
+	return(-1);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_ParmPresent() - checks if a given string was passed as a command
+//              line parameter at startup
+//
+///////////////////////////////////////////////////////////////////////////
+boolean
+US_ParmPresent(char *arg)
+{
+	int i;
+	char *strings[2];
+
+	strings[0] = arg;
+	strings[1] = NULL;
+
+	for (i=1; i<_argc; i++)
+	{
+		if (US_CheckParm(_argv[i], strings) != -1)
+			return true;
+	}
+	return false;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      USL_ScreenDraw() - Draws a chunk of the text screen (called only by
+//              US_TextScreen())
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+USL_ScreenDraw(word x,word y,char *s,byte attr)
+{
+	byte    far *screen,far *oscreen;
+
+	screen = MK_FP(0xb800,(x * 2) + (y * 80 * 2));
+	oscreen = (&introscn + 7) + ((x - 1) * 2) + (y * 80 * 2) + 1;
+	while (*s)
+	{
+		*screen++ = *s++;
+		if (attr != 0xff)
+		{
+			*screen++ = (attr & 0x8f) | (*oscreen & 0x70);
+			oscreen += 2;
+		}
+		else
+			screen++;
+	}
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      USL_ClearTextScreen() - Makes sure the screen is in text mode, clears it,
+//              and moves the cursor to the leftmost column of the bottom line
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+USL_ClearTextScreen(void)
+{
+	// Set to 80x25 color text mode
+	_AL = 3;                                // Mode 3
+	_AH = 0x00;
+	geninterrupt(0x10);
+
+	// Use BIOS to move the cursor to the bottom of the screen
+	_AH = 0x0f;
+	geninterrupt(0x10);             // Get current video mode into _BH
+	_DL = 0;                                // Lefthand side of the screen
+	_DH = 24;                               // Bottom row
+	_AH = 0x02;
+	geninterrupt(0x10);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_TextScreen() - Puts up the startup text screen
+//      Note: These are the only User Manager functions that can be safely called
+//              before the User Mgr has been started up
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_TextScreen(void)
+{
+	word    i,n;
+
+	USL_ClearTextScreen();
+
+	_fmemcpy(MK_FP(0xb800,0),7 + &introscn,80 * 25 * 2);
+
+	// Check for TED launching here
+	for (i = 1;i < _argc;i++)
+	{
+		n = US_CheckParm(_argv[i],ParmStrings);
+		if (n == 0)
+		{
+			tedlevelnum = atoi(_argv[i + 1]);
+			if (tedlevelnum >= 0)
+			{
+				tedlevel = true;
+				return;
+			}
+			else
+				break;
+		}
+		else if (n == 1)
+		{
+			NoWait = true;
+			return;
+		}
+	}
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      USL_Show() - Changes the appearance of one of the fields on the text
+//              screen. Possibly adds a checkmark in front of it and highlights it
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+USL_Show(word x,word y,word w,boolean show,boolean hilight)
+{
+	byte    far *screen,far *oscreen;
+
+	screen = MK_FP(0xb800,((x - 1) * 2) + (y * 80 * 2));
+	oscreen = (&introscn + 7) + ((x - 1) * 2) + (y * 80 * 2) - 1;
+	*screen++ = show? 251 : ' ';    // Checkmark char or space
+//      *screen = 0x48;
+//      *screen = (*oscreen & 0xf0) | 8;
+	oscreen += 2;
+	if (show && hilight)
+	{
+		for (w++;w--;screen += 2,oscreen += 2)
+			*screen = (*oscreen & 0xf0) | 0x0f;
+	}
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      USL_ShowMem() - Right justifies a longword in one of the memory fields on
+//              the text screen
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+USL_ShowMem(word x,word y,long mem)
+{
+	char    buf[16];
+	word    i;
+
+	for (i = strlen(ltoa(mem,buf,10));i < 5;i++)
+		USL_ScreenDraw(x++,y," ",0xff);
+	USL_ScreenDraw(x,y,buf,0xff);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_UpdateTextScreen() - Called after the ID libraries are started up.
+//              Displays what hardware is present.
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_UpdateTextScreen(void)
+{
+	boolean         b;
+	longword        totalmem;
+
+	// Show video card info
+	b = (grmode == CGAGR);
+	USL_Show(21,7,4,(videocard >= CGAcard) && (videocard <= VGAcard),b);
+	b = (grmode == EGAGR || grmode == VGAGR);
+	USL_Show(21,8,7,(videocard >= EGAcard) && (videocard <= VGAcard),b);
+//	b = (grmode == VGAGR);
+//	USL_Show(21,9,4,videocard == VGAcard,b);
+#if GRMODE != CGAGR
+	if (compatability)
+		USL_ScreenDraw(5,10,"SVGA Compatibility Mode Enabled.",0x4f);
+#endif
+
+	// Show input device info
+	USL_Show(60,7,8,true,true);
+	USL_Show(60,8,11,JoysPresent[0],true);
+	USL_Show(60,9,11,JoysPresent[1],true);
+	USL_Show(60,10,5,MousePresent,true);
+
+	// Show sound hardware info
+	USL_Show(21,14,11,true,SoundMode == sdm_PC);
+	b = (SoundMode == sdm_AdLib) || (MusicMode == smm_AdLib);
+	USL_Show(21,15,14,AdLibPresent,b);
+	if (b && AdLibPresent)  // Hack because of two lines
+	{
+		byte    far *screen,far *oscreen;
+		word    x,y,w;
+
+		x = 21;
+		y = 16;
+		w = 14;
+		screen = MK_FP(0xb800,(x * 2) + (y * 80 * 2) - 1);
+		oscreen = (&introscn + 7) + (x * 2) + (y * 80 * 2) - 1;
+		oscreen += 2;
+		for (w++;w--;screen += 2,oscreen += 2)
+			*screen = (*oscreen & 0xf0) | 0x0f;
+	}
+
+	// Show memory available/used
+	USL_ShowMem(63,15,mminfo.mainmem / 1024);
+	USL_Show(53,15,23,true,true);
+	USL_ShowMem(63,16,mminfo.EMSmem / 1024);
+	USL_Show(53,16,23,mminfo.EMSmem? true : false,true);
+	USL_ShowMem(63,17,mminfo.XMSmem / 1024);
+	USL_Show(53,17,23,mminfo.XMSmem? true : false,true);
+	totalmem = mminfo.mainmem + mminfo.EMSmem + mminfo.XMSmem;
+	USL_ShowMem(63,18,totalmem / 1024);
+	USL_Show(53,18,23,true,true);   // DEBUG
+	USL_ScreenDraw(52,18," ",0xff);
+
+	// Change Initializing... to Loading...
+	USL_ScreenDraw(27,22,"  Loading...   ",0x9c);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_FinishTextScreen() - After the main program has finished its initial
+//              loading, this routine waits for a keypress and then clears the screen
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_FinishTextScreen(void)
+{
+static  byte    colors[] = {4,6,13,15,15,15,15,15,15};
+		boolean up;
+		int             i,c;
+
+	// Change Loading... to Press a Key
+
+	if (!(tedlevel || NoWait))
+	{
+		IN_ClearKeysDown();
+		for (i = 0,up = true;!IN_UserInput(4,true);)
+		{
+			c = colors[i];
+			if (up)
+			{
+				if (++i == 9)
+					i = 8,up = false;
+			}
+			else
+			{
+				if (--i < 0)
+					i = 1,up = true;
+			}
+
+			USL_ScreenDraw(29,22," Ready - Press a Key     ",0x00 + c);
+		}
+	}
+	else
+		USL_ScreenDraw(29,22," Ready - Press a Key     ",0x9a);
+
+	IN_ClearKeysDown();
+
+	USL_ClearTextScreen();
+}
+
+//      Window/Printing routines
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_SetPrintRoutines() - Sets the routines used to measure and print
+//              from within the User Mgr. Primarily provided to allow switching
+//              between masked and non-masked fonts
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_SetPrintRoutines(void (*measure)(char far *,word *,word *),void (*print)(char far *))
+{
+	USL_MeasureString = measure;
+	USL_DrawString = print;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_Print() - Prints a string in the current window. Newlines are
+//              supported.
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_Print(char *s)
+{
+	char    c,*se;
+	word    w,h;
+
+	while (*s)
+	{
+		se = s;
+		while ((c = *se) && (c != '\n'))
+			se++;
+		*se = '\0';
+
+		USL_MeasureString(s,&w,&h);
+		px = PrintX;
+		py = PrintY;
+		USL_DrawString(s);
+
+		s = se;
+		if (c)
+		{
+			*se = c;
+			s++;
+
+			PrintX = WindowX;
+			PrintY += h;
+		}
+		else
+			PrintX += w;
+	}
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_PrintUnsigned() - Prints an unsigned long
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_PrintUnsigned(longword n)
+{
+	char    buffer[32];
+
+	US_Print(ultoa(n,buffer,10));
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_PrintSigned() - Prints a signed long
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_PrintSigned(long n)
+{
+	char    buffer[32];
+
+	US_Print(ltoa(n,buffer,10));
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      USL_PrintInCenter() - Prints a string in the center of the given rect
+//
+///////////////////////////////////////////////////////////////////////////
+void
+USL_PrintInCenter(char *s,Rect r)
+{
+	word    w,h,
+			rw,rh;
+
+	USL_MeasureString(s,&w,&h);
+	rw = r.lr.x - r.ul.x;
+	rh = r.lr.y - r.ul.y;
+
+	px = r.ul.x + ((rw - w) / 2);
+	py = r.ul.y + ((rh - h) / 2);
+	USL_DrawString(s);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_PrintCentered() - Prints a string centered in the current window.
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_PrintCentered(char *s)
+{
+	Rect    r;
+
+	r.ul.x = WindowX;
+	r.ul.y = WindowY;
+	r.lr.x = r.ul.x + WindowW;
+	r.lr.y = r.ul.y + WindowH;
+
+	USL_PrintInCenter(s,r);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_CPrintLine() - Prints a string centered on the current line and
+//              advances to the next line. Newlines are not supported.
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_CPrintLine(char *s)
+{
+	word    w,h;
+
+	USL_MeasureString(s,&w,&h);
+
+	if (w > WindowW)
+		Quit("US_CPrintLine() - String exceeds width");
+	px = WindowX + ((WindowW - w) / 2);
+	py = PrintY;
+	USL_DrawString(s);
+	PrintY += h;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_CPrint() - Prints a string in the current window. Newlines are
+//              supported.
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_CPrint(char *s)
+{
+	char    c,*se;
+
+	while (*s)
+	{
+		se = s;
+		while ((c = *se) && (c != '\n'))
+			se++;
+		*se = '\0';
+
+		US_CPrintLine(s);
+
+		s = se;
+		if (c)
+		{
+			*se = c;
+			s++;
+		}
+	}
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_ClearWindow() - Clears the current window to white and homes the
+//              cursor
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_ClearWindow(void)
+{
+	VWB_Bar(WindowX,WindowY,WindowW,WindowH,WHITE);
+	PrintX = WindowX;
+	PrintY = WindowY;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_DrawWindow() - Draws a frame and sets the current window parms
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_DrawWindow(word x,word y,word w,word h)
+{
+	word    i,
+			sx,sy,sw,sh;
+
+	WindowX = x * 8;
+	WindowY = y * 8;
+	WindowW = w * 8;
+	WindowH = h * 8;
+
+	PrintX = WindowX;
+	PrintY = WindowY;
+
+	sx = (x - 1) * 8;
+	sy = (y - 1) * 8;
+	sw = (w + 1) * 8;
+	sh = (h + 1) * 8;
+
+	US_ClearWindow();
+
+	VWB_DrawTile8M(sx,sy,0),VWB_DrawTile8M(sx,sy + sh,6);
+	for (i = sx + 8;i <= sx + sw - 8;i += 8)
+		VWB_DrawTile8M(i,sy,1),VWB_DrawTile8M(i,sy + sh,7);
+	VWB_DrawTile8M(i,sy,2),VWB_DrawTile8M(i,sy + sh,8);
+
+	for (i = sy + 8;i <= sy + sh - 8;i += 8)
+		VWB_DrawTile8M(sx,i,3),VWB_DrawTile8M(sx + sw,i,5);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_CenterWindow() - Generates a window of a given width & height in the
+//              middle of the screen
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_CenterWindow(word w,word h)
+{
+	US_DrawWindow(((MaxX / 8) - w) / 2,((MaxY / 8) - h) / 2,w,h);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_CenterSaveWindow() - Generates a window of a given width & height in
+//              the middle of the screen, saving the background
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_CenterSaveWindow(word w,word h,memptr *save)
+{
+	word    x,y,
+			screen;
+
+	x = ((MaxX / 8) - w) / 2;
+	y = ((MaxY / 8) - h) / 2;
+	MM_GetPtr(save,(w * h) * CHARWIDTH);
+	screen = bufferofs + panadjust + ylookup[y] + (x * CHARWIDTH);
+	VW_ScreenToMem(screen,*save,w * CHARWIDTH,h);
+	US_DrawWindow(((MaxX / 8) - w) / 2,((MaxY / 8) - h) / 2,w,h);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_RestoreSaveWindow() - Restores the background of the size of the
+//              current window from the memory specified by save
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_RestoreSaveWindow(memptr *save)
+{
+	word    screen;
+
+	screen = bufferofs + panadjust + ylookup[WindowY] + (WindowX * CHARWIDTH);
+	VW_MemToScreen(*save,screen,WindowW * CHARWIDTH,WindowH);
+	MM_FreePtr(save);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_SaveWindow() - Saves the current window parms into a record for
+//              later restoration
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_SaveWindow(WindowRec *win)
+{
+	win->x = WindowX;
+	win->y = WindowY;
+	win->w = WindowW;
+	win->h = WindowH;
+
+	win->px = PrintX;
+	win->py = PrintY;
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_RestoreWindow() - Sets the current window parms to those held in the
+//              record
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_RestoreWindow(WindowRec *win)
+{
+	WindowX = win->x;
+	WindowY = win->y;
+	WindowW = win->w;
+	WindowH = win->h;
+
+	PrintX = win->px;
+	PrintY = win->py;
+}
+
+//      Cursor routines
+
+#if 0
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_StartCursor() - Sets up the cursor for User Mgr use
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_StartCursor(void)
+{
+	CursorInfo      info;
+
+	VW_SetCursor(CURSORARROWSPR);
+	CursorX = MaxX / 2;
+	CursorY = MaxY / 2;
+	VW_MoveCursor(CursorX,CursorY);
+	VW_ShowCursor();
+
+	IN_ReadCursor(&info);   // Dispose of any accumulated movement
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_ShutCursor() - Cleans up after US_StartCursor()
+//
+///////////////////////////////////////////////////////////////////////////
+void
+US_ShutCursor(void)
+{
+	VW_HideCursor();
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_UpdateCursor() - Gets the new cursor position & button states from
+//              the Input Mgr and tells the View Mgr where the cursor is
+//
+///////////////////////////////////////////////////////////////////////////
+boolean
+US_UpdateCursor(void)
+{
+	CursorInfo      info;
+
+	IN_ReadCursor(&info);
+	if (info.x || info.y || CursorBad)
+	{
+		CursorX += info.x;
+		if (CursorX >= MaxX)
+			CursorX = MaxX - 1;
+		else if (CursorX < 0)
+			CursorX = 0;
+
+		CursorY += info.y;
+		if (CursorY >= MaxY)
+			CursorY = MaxY - 1;
+		else if (CursorY < 0)
+			CursorY = 0;
+
+		VW_MoveCursor(CursorX,CursorY);
+		CursorBad = false;
+	}
+	Button0 = info.button0;
+	Button1 = info.button1;
+	return(Button0 || Button1);
+}
+#endif
+
+//      Input routines
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      USL_XORICursor() - XORs the I-bar text cursor. Used by US_LineInput()
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+USL_XORICursor(int x,int y,char *s,word cursor)
+{
+	char    buf[MaxString];
+	word    w,h;
+
+	strcpy(buf,s);
+	buf[cursor] = '\0';
+	USL_MeasureString(buf,&w,&h);
+
+	px = x + w - 1;
+	py = y;
+	USL_DrawString("\x80");
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_LineInput() - Gets a line of user input at (x,y), the string defaults
+//              to whatever is pointed at by def. Input is restricted to maxchars
+//              chars or maxwidth pixels wide. If the user hits escape (and escok is
+//              true), nothing is copied into buf, and false is returned. If the
+//              user hits return, the current string is copied into buf, and true is
+//              returned
+//
+///////////////////////////////////////////////////////////////////////////
+boolean
+US_LineInput(int x,int y,char *buf,char *def,boolean escok,
+				int maxchars,int maxwidth)
+{
+	boolean         redraw,
+				cursorvis,cursormoved,
+				done,result;
+	ScanCode        sc;
+	char            c,
+				s[MaxString],olds[MaxString];
+	word            i,
+				cursor,
+				w,h,
+				len;
+	longword        lasttime;
+
+	VW_HideCursor();
+
+	if (def)
+		strcpy(s,def);
+	else
+		*s = '\0';
+	*olds = '\0';
+	cursor = strlen(s);
+	cursormoved = redraw = true;
+
+	cursorvis = done = false;
+	lasttime = TimeCount;
+	LastASCII = key_None;
+	LastScan = sc_None;
+
+	while (!done)
+	{
+		if (cursorvis)
+			USL_XORICursor(x,y,s,cursor);
+
+	asm     pushf
+	asm     cli
+
+		sc = LastScan;
+		LastScan = sc_None;
+		c = LastASCII;
+		LastASCII = key_None;
+
+	asm     popf
+
+		switch (sc)
+		{
+		case sc_LeftArrow:
+			if (cursor)
+				cursor--;
+			c = key_None;
+			cursormoved = true;
+			break;
+		case sc_RightArrow:
+			if (s[cursor])
+				cursor++;
+			c = key_None;
+			cursormoved = true;
+			break;
+		case sc_Home:
+			cursor = 0;
+			c = key_None;
+			cursormoved = true;
+			break;
+		case sc_End:
+			cursor = strlen(s);
+			c = key_None;
+			cursormoved = true;
+			break;
+
+		case sc_Return:
+			strcpy(buf,s);
+			done = true;
+			result = true;
+			c = key_None;
+			break;
+		case sc_Escape:
+			if (escok)
+			{
+				done = true;
+				result = false;
+			}
+			c = key_None;
+			break;
+
+		case sc_BackSpace:
+			if (cursor)
+			{
+				strcpy(s + cursor - 1,s + cursor);
+				cursor--;
+				redraw = true;
+			}
+			c = key_None;
+			cursormoved = true;
+			break;
+		case sc_Delete:
+			if (s[cursor])
+			{
+				strcpy(s + cursor,s + cursor + 1);
+				redraw = true;
+			}
+			c = key_None;
+			cursormoved = true;
+			break;
+
+		case 0x4c:      // Keypad 5
+		case sc_UpArrow:
+		case sc_DownArrow:
+		case sc_PgUp:
+		case sc_PgDn:
+		case sc_Insert:
+			c = key_None;
+			break;
+		}
+
+		if (c)
+		{
+			len = strlen(s);
+			USL_MeasureString(s,&w,&h);
+
+			if
+			(
+				isprint(c)
+			&&      (len < MaxString - 1)
+			&&      ((!maxchars) || (len < maxchars))
+			&&      ((!maxwidth) || (w < maxwidth))
+			)
+			{
+				for (i = len + 1;i > cursor;i--)
+					s[i] = s[i - 1];
+				s[cursor++] = c;
+				redraw = true;
+			}
+		}
+
+		if (redraw)
+		{
+			px = x;
+			py = y;
+			USL_DrawString(olds);
+			strcpy(olds,s);
+
+			px = x;
+			py = y;
+			USL_DrawString(s);
+
+			redraw = false;
+		}
+
+		if (cursormoved)
+		{
+			cursorvis = false;
+			lasttime = TimeCount - TickBase;
+
+			cursormoved = false;
+		}
+		if (TimeCount - lasttime > TickBase / 2)
+		{
+			lasttime = TimeCount;
+
+			cursorvis ^= true;
+		}
+		if (cursorvis)
+			USL_XORICursor(x,y,s,cursor);
+
+		VW_UpdateScreen();
+	}
+
+	if (cursorvis)
+		USL_XORICursor(x,y,s,cursor);
+	if (!result)
+	{
+		px = x;
+		py = y;
+		USL_DrawString(olds);
+	}
+	VW_ShowCursor();
+	VW_UpdateScreen();
+
+	IN_ClearKeysDown();
+	return(result);
+}
diff --git a/16/keen456/KEEN4-6/ID_US_2.C b/16/keen456/KEEN4-6/ID_US_2.C
new file mode 100755
index 00000000..e1948616
--- /dev/null
+++ b/16/keen456/KEEN4-6/ID_US_2.C
@@ -0,0 +1,2260 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+//
+//      ID Engine
+//      ID_US.c - User Manager - User interface
+//      v1.1d1
+//      By Jason Blochowiak
+//      Hacked up for Catacomb 3D
+//
+
+#include "ID_HEADS.H"
+#pragma hdrstop
+
+#pragma warn    -pia
+
+//      Special imports
+extern  boolean         showscorebox;
+#ifdef  KEEN
+extern	boolean		jerk;
+extern  boolean         oldshooting;
+extern  ScanCode        firescan;
+void	USL_CheckSavedGames(void);
+#else
+		ScanCode        firescan;
+#endif
+
+//      Global variables
+		boolean         ingame,abortgame,loadedgame;
+		GameDiff        restartgame = gd_Continue;
+
+//      Internal variables
+static  boolean         GameIsDirty,
+					QuitToDos,
+					CtlPanelDone;
+
+#ifdef KEEN6
+	int		listindex = -1;
+	boolean		checkpassed;
+#endif
+
+//      Forward reference prototypes
+static void     USL_SetupCard(void);
+
+//      Control panel data
+
+#define CtlPanelSX      74
+#define CtlPanelSY      48
+#define CtlPanelEX      234
+#define CtlPanelEY      150
+#define CtlPanelW       (CtlPanelEX - CtlPanelSX)
+#define CtlPanelH       (CtlPanelEY - CtlPanelSY)
+
+#ifdef KEEN
+
+#define TileBase        92
+
+#if GRMODE == CGAGR
+
+#define BackColor               0
+#define HiliteColor             (BackColor ^ 3)
+#define NohiliteColor   (BackColor ^ 2)
+
+#else
+
+#define BackColor               8
+#define HiliteColor             (BackColor ^ 10)
+#define NohiliteColor   (BackColor ^ 2)
+
+#endif	// if GRMODE == CGAGR ... else ...
+
+#else	// ifdef KEEN
+
+#define TileBase        92
+
+// DEBUG - CGA
+#define BackColor               0
+#define HiliteColor             (BackColor ^ 12)
+#define NohiliteColor   (BackColor ^ 4)
+
+#endif
+
+typedef enum
+		{
+			uc_None,
+			uc_Return,
+			uc_Abort,
+			uc_Quit,
+			uc_Loaded,
+			uc_SEasy,
+			uc_SNormal,
+			uc_SHard,
+		} UComm;
+typedef enum
+		{
+			uii_Bad,
+			uii_Button,uii_RadioButton,uii_Folder
+		} UIType;
+typedef enum
+		{
+			ui_Normal = 0,
+			ui_Pushed = 1,
+			ui_Selected = 2,
+			ui_Disabled = 4,
+			ui_Separated = 8
+		} UIFlags;
+#define UISelectFlags (ui_Pushed | ui_Selected | ui_Disabled)
+
+typedef enum
+		{
+			uic_SetupCard,uic_DrawCard,uic_TouchupCard,
+			uic_DrawIcon,uic_Draw,uic_Hit
+		} UserCall;
+
+typedef struct  UserItem
+		{
+				UIType                  type;
+				UIFlags                 flags;
+				ScanCode                hotkey;
+				char                    *text;
+				UComm                   comm;
+				void                    far *child;     // Should be (UserItemGroup *)
+
+				word                    x,y;
+		} UserItem;
+typedef struct  UserItemGroup
+		{
+				word                    x,y;
+				graphicnums             title;
+				ScanCode                hotkey;
+				UserItem                far *items;
+				boolean                 (*custom)(UserCall,struct UserItem far *);      // Custom routine
+
+				word                    cursor;
+		struct  UserItemGroup   far *parent;
+		} UserItemGroup;
+
+static  char            *BottomS1,*BottomS2,*BottomS3;
+static  UComm           Communication;
+static  ScanCode        *KeyMaps[] =
+					{
+						&KbdDefs[0].button0,
+						&KbdDefs[0].button1,
+						&firescan,
+						&KbdDefs[0].upleft,
+						&KbdDefs[0].up,
+						&KbdDefs[0].upright,
+						&KbdDefs[0].right,
+						&KbdDefs[0].downright,
+						&KbdDefs[0].down,
+						&KbdDefs[0].downleft,
+						&KbdDefs[0].left
+					};
+
+// Custom routine prototypes
+static  boolean USL_ConfigCustom(UserCall call,struct UserItem far *item),
+				USL_KeyCustom(UserCall call,struct UserItem far *item),
+				USL_KeySCustom(UserCall call,struct UserItem far *item),
+				USL_Joy1Custom(UserCall call,struct UserItem far *item),
+				USL_Joy2Custom(UserCall call,struct UserItem far *item),
+				USL_JoyGCustom(UserCall call,struct UserItem far *item),
+				USL_LoadCustom(UserCall call,struct UserItem far *item),
+				USL_SaveCustom(UserCall call,struct UserItem far *item),
+				USL_ScoreCustom(UserCall call,struct UserItem far *item),
+				USL_CompCustom(UserCall call,struct UserItem far *item),
+				USL_SmoothCustom(UserCall call,struct UserItem far *item),
+#ifdef KEEN
+				USL_TwoCustom(UserCall call,struct UserItem far *item),
+#endif
+				USL_PongCustom(UserCall call,struct UserItem far *item);
+
+#define DefButton(key,text)                             uii_Button,ui_Normal,key,text
+#define DefRButton(key,text)                    uii_RadioButton,ui_Normal,key,text
+#define DefFolder(key,text,child)               uii_Folder,ui_Normal,key,text,uc_None,child
+#define CustomGroup(title,key,custom)   0,0,title,key,0,custom
+	UserItem far holder[] =
+	{
+		{DefButton(sc_None,"DEBUG")},
+		{uii_Bad}
+	};
+	UserItemGroup   far holdergroup = {0,0,CP_MAINMENUPIC,sc_None,holder};
+
+	// Sound menu
+	UserItem far soundi[] =
+	{
+		{DefRButton(sc_N,"NO SOUND EFFECTS")},
+		{DefRButton(sc_P,"PC SPEAKER")},
+		{DefRButton(sc_A,"ADLIB/SOUNDBLASTER")},
+		{DefRButton(sc_Q,"QUIET ADLIB/SOUNDBLASTER")},
+		{uii_Bad}
+	};
+	UserItemGroup   far soundgroup = {8,0,CP_SOUNDMENUPIC,sc_None,soundi};
+
+	// Music menu
+	UserItem far musici[] =
+	{
+		{DefRButton(sc_N,"NO MUSIC")},
+		{DefRButton(sc_A,"ADLIB/SOUNDBLASTER")},
+		{uii_Bad}
+	};
+	UserItemGroup   far musicgroup = {8,0,CP_MUSICMENUPIC,sc_None,musici};
+
+	// New game menu
+	UserItem far newgamei[] =
+	{
+		{DefButton(sc_E,"BEGIN EASY GAME"),uc_SEasy},
+		{DefButton(sc_N,"BEGIN NORMAL GAME"),uc_SNormal},
+		{DefButton(sc_H,"BEGIN HARD GAME"),uc_SHard},
+		{uii_Bad}
+	};
+	UserItemGroup   far newgamegroup = {8,0,CP_NEWGAMEMENUPIC,sc_None,newgamei,0,1};
+
+	// Load/Save game menu
+	UserItem far loadsavegamei[] =
+	{
+#ifdef CAT3D
+		{uii_Button,ui_Normal,sc_None},
+		{uii_Button,ui_Normal,sc_None},
+		{uii_Button,ui_Normal,sc_None},
+		{uii_Button,ui_Normal,sc_None},
+		{uii_Button,ui_Normal,sc_None},
+		{uii_Button,ui_Normal,sc_None},
+#else
+		{uii_Button,ui_Normal,sc_1},
+		{uii_Button,ui_Normal,sc_2},
+		{uii_Button,ui_Normal,sc_3},
+		{uii_Button,ui_Normal,sc_4},
+		{uii_Button,ui_Normal,sc_5},
+		{uii_Button,ui_Normal,sc_6},
+#endif
+		{uii_Bad}
+	};
+	UserItemGroup   far loadgamegroup = {4,3,CP_LOADMENUPIC,sc_None,loadsavegamei,USL_LoadCustom};
+	UserItemGroup   far savegamegroup = {4,3,CP_SAVEMENUPIC,sc_None,loadsavegamei,USL_SaveCustom};
+
+	// Options menu
+	UserItemGroup   far scoregroup = {0,0,0,sc_None,0,USL_ScoreCustom};
+#ifdef KEEN
+	UserItemGroup   far twogroup = {0,0,0,sc_None,0,USL_TwoCustom};
+#endif
+#if GRMODE != CGAGR
+	UserItemGroup   far smoothgroup = {0,0,0,sc_None,0,USL_SmoothCustom};
+	UserItemGroup   far compgroup = {0,0,0,sc_None,0,USL_CompCustom};
+#endif
+
+	UserItem far optionsi[] =
+	{
+		{DefFolder(sc_S,"",&scoregroup)},
+#ifdef KEEN
+		{DefFolder(sc_T,"",&twogroup)},
+#endif
+#if GRMODE != CGAGR
+		{DefFolder(sc_M,"",&smoothgroup)},
+		{DefFolder(sc_C,"",&compgroup)},
+#endif
+		{uii_Bad}
+	};
+	UserItemGroup   far optionsgroup = {8,0,CP_OPTIONSMENUPIC,sc_None,optionsi};
+
+	// Keyboard menu
+	UserItem far keyi[] =
+	{
+		{DefButton(sc_None,"UP & LEFT")},
+		{DefButton(sc_None,"UP")},
+		{DefButton(sc_None,"UP & RIGHT")},
+		{DefButton(sc_None,"RIGHT")},
+		{DefButton(sc_None,"DOWN & RIGHT")},
+		{DefButton(sc_None,"DOWN")},
+		{DefButton(sc_None,"DOWN & LEFT")},
+		{DefButton(sc_None,"LEFT")},
+		{uii_Bad}
+	};
+	UserItemGroup   far keygroup = {0,0,CP_KEYMOVEMENTPIC,sc_None,keyi,USL_KeyCustom};
+	UserItem far keybi[] =
+	{
+#ifdef  KEEN
+		{DefButton(sc_J,"JUMP")},
+		{DefButton(sc_P,"POGO")},
+		{DefButton(sc_F,"FIRE")},
+#endif
+#ifdef  CAT3D
+		{DefButton(sc_J,"FIRE")},
+		{DefButton(sc_P,"STRAFE")},
+#endif
+#ifdef  CPD
+		{DefButton(sc_J,"SHOOT")},
+		{DefButton(sc_P,"BOMB")},
+#endif
+		{uii_Bad}
+	};
+	UserItemGroup   far keybgroup = {0,0,CP_KEYBUTTONPIC,sc_None,keybi,USL_KeyCustom};
+	UserItem far keysi[] =
+	{
+		{DefFolder(sc_M,"MOVEMENT",&keygroup)},
+		{DefFolder(sc_B,"BUTTONS",&keybgroup)},
+		{uii_Bad}
+	};
+	UserItemGroup   far keysgroup = {8,0,CP_KEYBOARDMENUPIC,sc_None,keysi,USL_KeySCustom};
+
+	// Joystick #1 & #2
+	UserItemGroup   far joy1group = {CustomGroup(CP_JOYSTICKMENUPIC,sc_None,USL_Joy1Custom)};
+	UserItemGroup   far joy2group = {CustomGroup(CP_JOYSTICKMENUPIC,sc_None,USL_Joy2Custom)};
+	UserItemGroup   far gravisgroup = {CustomGroup(CP_JOYSTICKMENUPIC,sc_None,USL_JoyGCustom)};
+
+	// Config menu
+	UserItem far configi[] =
+	{
+		{DefFolder(sc_S,"SOUND",&soundgroup)},
+		{DefFolder(sc_M,"MUSIC",&musicgroup)},
+#ifndef CAT3D
+		{DefFolder(sc_O,"OPTIONS",&optionsgroup)},
+#endif
+		{uii_Folder,ui_Separated,sc_K,"USE KEYBOARD",uc_None,&keysgroup},
+		{DefFolder(sc_1,"USE JOYSTICK #1",&joy1group)},
+		{DefFolder(sc_2,"USE JOYSTICK #2",&joy2group)},
+		{DefFolder(sc_G,"",&gravisgroup)},
+		{uii_Bad}
+	};
+#ifdef CAT3D
+	UserItemGroup   far configgroup = {8,0,CP_CONFIGMENUPIC,sc_None,configi,USL_ConfigCustom};
+#else
+	UserItemGroup   far configgroup = {0,0,CP_CONFIGMENUPIC,sc_None,configi,USL_ConfigCustom};
+#endif
+
+	// Main menu
+	UserItemGroup   far ponggroup = {0,0,0,sc_None,0,USL_PongCustom};
+	UserItem far rooti[] =
+	{
+		{DefFolder(sc_N,"NEW GAME",&newgamegroup)},
+		{DefFolder(sc_L,"LOAD GAME",&loadgamegroup)},
+		{DefFolder(sc_S,"SAVE GAME",&savegamegroup)},
+		{DefFolder(sc_C,"CONFIGURE",&configgroup)},
+		{DefButton(sc_R,nil),uc_Return},        // Return to Game/Demo
+		{DefButton(sc_E,"END GAME"),uc_Abort},
+#ifdef KEEN
+		{DefFolder(sc_P,"PADDLE WAR",&ponggroup)},
+#elif defined CAT3D
+		{DefFolder(sc_B,"SKULL 'N' BONES",&ponggroup)},
+#endif
+		{DefButton(sc_Q,"QUIT"),uc_Quit},
+		{uii_Bad}
+	};
+	UserItemGroup   far rootgroup = {32,4,CP_MAINMENUPIC,sc_None,rooti};
+#undef  DefButton
+#undef  DefFolder
+
+#define MaxCards        7
+	word                    cstackptr;
+	UserItemGroup   far *cardstack[MaxCards],
+					far *topcard;
+
+//      Card stack code
+static void
+USL_SetupStack(void)
+{
+	cstackptr = 0;
+	cardstack[0] = topcard = &rootgroup;
+}
+
+static void
+USL_PopCard(void)
+{
+	if (!cstackptr)
+		return;
+
+	topcard = cardstack[--cstackptr];
+}
+
+static void
+USL_PushCard(UserItemGroup far *card)
+{
+	if (cstackptr == MaxCards - 1)
+		return;
+
+	topcard = cardstack[++cstackptr] = card;
+}
+
+static void
+USL_DrawItemIcon(UserItem far *item)
+{
+	word    flags,tile;
+
+	if (topcard->custom && topcard->custom(uic_DrawIcon,item))
+		return;
+
+	flags = item->flags;
+	if (flags & ui_Disabled)
+		tile = TileBase + ((flags & ui_Selected)? 5 : 4);
+	else if ((item->type == uii_RadioButton) && (!(flags & ui_Pushed)))
+		tile = TileBase + ((flags & ui_Selected)? 3 : 2);
+	else
+		tile = TileBase + ((flags & ui_Selected)? 1 : 0);
+	VWB_DrawTile8(item->x,item->y,tile);
+}
+
+static void
+USL_DrawItem(UserItem far *item)
+{
+	if (topcard->custom && topcard->custom(uic_Draw,item))
+		return;
+
+	VWB_Bar(CtlPanelSX + 1,item->y,
+			CtlPanelEX - CtlPanelSX - 1,8,BackColor);       // Clear out background
+	USL_DrawItemIcon(item);
+	if ((item->flags & ui_Selected) && !(item->flags & ui_Disabled))
+		fontcolor = HiliteColor;
+	else
+		fontcolor = NohiliteColor;
+	px = item->x + 8;
+	py = item->y + 1;
+	USL_DrawString(item->text);
+	fontcolor = F_BLACK;
+}
+
+#ifdef KEEN
+#if GRMODE == CGAGR
+#define MyLine(y)       VWB_Hlin(CtlPanelSX + 3,CtlPanelEX - 3,y,3);
+#else
+#define MyLine(y)       VWB_Hlin(CtlPanelSX + 3,CtlPanelEX - 3,y,10);
+#endif
+#else
+#define MyLine(y)       VWB_Hlin(CtlPanelSX + 3,CtlPanelEX - 3,y,12);
+#endif
+
+static void
+USL_DrawBottom(void)
+{
+	word    w,h;
+
+	fontcolor = NohiliteColor;
+
+	px = CtlPanelSX + 4;
+	py = CtlPanelEY - 15;
+	USL_DrawString(BottomS1);
+
+	USL_MeasureString(BottomS2,&w,&h);
+	px = CtlPanelEX - 4 - w;
+	USL_DrawString(BottomS2);
+
+	USL_MeasureString(BottomS3,&w,&h);
+	px = CtlPanelSX + ((CtlPanelEX - CtlPanelSX - w) / 2);
+	py += h + 1;
+	USL_DrawString(BottomS3);
+
+	fontcolor = F_WHITE;
+	MyLine(CtlPanelEY - 17);
+}
+
+static void
+USL_DrawCtlPanelContents(void)
+{
+	int                             x,y;
+	UserItem                far *item;
+
+	if (topcard->custom && topcard->custom(uic_DrawCard,nil))
+		return;
+
+	if (topcard->title)
+	{
+		// Draw the title
+		MyLine(CtlPanelSY + 7);
+		VWB_DrawPic(CtlPanelSX + 6,CtlPanelSY,topcard->title);
+	}
+
+	USL_DrawBottom();
+
+	if (!topcard->items)
+		return;
+
+	x = topcard->x + CtlPanelSX;
+	if (x % 8)
+		x += 8 - (x % 8);
+	y = topcard->y + CtlPanelSY + 12;
+	for (item = topcard->items;item->type != uii_Bad;item++)
+	{
+		if (item->flags & ui_Separated)
+			y += 8;
+
+		item->x = x;
+		item->y = y;
+		USL_DrawItem(item);
+		y += 8;
+	}
+	if (topcard->custom)
+		topcard->custom(uic_TouchupCard,nil);
+}
+
+static void
+USL_DrawCtlPanel(void)
+{
+	if (topcard->items || topcard->title)
+	{
+		// Draw the backdrop
+		VWB_DrawPic(0,0,CP_MENUSCREENPIC);
+
+		// Draw the contents
+		USL_DrawCtlPanelContents();
+	}
+
+	// Refresh the screen
+	VW_UpdateScreen();
+}
+
+static void
+USL_DialogSetup(word w,word h,word *x,word *y)
+{
+	VWB_DrawMPic(CtlPanelSX,CtlPanelSY,CP_MENUMASKPICM);
+
+	*x = CtlPanelSX + ((CtlPanelW - w) / 2);
+	*y = CtlPanelSY + ((CtlPanelH - h) / 2);
+	VWB_Bar(*x,*y,w + 1,h + 1,BackColor);
+	VWB_Hlin(*x - 1,*x + w + 1,*y - 1,NohiliteColor);
+	VWB_Hlin(*x - 1,*x + w + 1,*y + h + 1,NohiliteColor);
+	VWB_Vlin(*y - 1,*y + h + 1,*x - 1,NohiliteColor);
+	VWB_Vlin(*y - 1,*y + h + 1,*x + w + 1,NohiliteColor);
+}
+
+static void
+USL_ShowLoadSave(char *s,char *name)
+{
+	word    x,y,
+			w,h,
+			tw,sw;
+	char    msg[MaxGameName + 4];
+
+	strcpy(msg,"'");
+	strcat(msg,name);
+	strcat(msg,"'");
+	USL_MeasureString(s,&sw,&h);
+	USL_MeasureString(msg,&w,&h);
+	tw = ((sw > w)? sw : w) + 6;
+	USL_DialogSetup(tw,(h * 2) + 2,&x,&y);
+	py = y + 2;
+	px = x + ((tw - sw) / 2);
+	USL_DrawString(s);
+	py += h;
+	px = x + ((tw - w) / 2);
+	USL_DrawString(msg);
+
+	VW_UpdateScreen();
+#ifdef CAT3D
+	IN_UserInput(100, true);
+#endif
+}
+
+static boolean
+USL_CtlDialog(char *s1,char *s2,char *s3)
+{
+	word            w,h,sh,
+				w1,w2,w3,
+				x,y;
+	ScanCode        c;
+	CursorInfo      cursorinfo;
+
+	USL_MeasureString(s1,&w1,&h);
+	USL_MeasureString(s2,&w2,&h);
+	if (s3)
+		USL_MeasureString(s3,&w3,&h);
+	else
+		w3 = 0;
+	w = (w1 > w2)? ((w1 > w3)? w1 : w3) : ((w2 > w3)? w2 : w3);
+	w += 7;
+	sh = h;
+	h *= s3? 5 : 4;
+
+	USL_DialogSetup(w,h,&x,&y);
+
+	fontcolor = HiliteColor;
+	px = x + ((w - w1) / 2);
+	py = y + sh + 1;
+	USL_DrawString(s1);
+	py += (sh * 2) - 1;
+
+	VWB_Hlin(x + 3,x + w - 3,py,NohiliteColor);
+	py += 2;
+
+	fontcolor = NohiliteColor;
+	px = x + ((w - w2) / 2);
+	USL_DrawString(s2);
+	py += sh;
+
+	if (s3)
+	{
+		px = x + ((w - w3) / 2);
+		USL_DrawString(s3);
+	}
+
+	VW_UpdateScreen();
+
+	IN_ClearKeysDown();
+	do
+	{
+		IN_ReadCursor(&cursorinfo);
+		if (cursorinfo.button0)
+			c = sc_Y;
+		else if (cursorinfo.button1)
+			c = sc_Escape;
+		else
+			c = LastScan;
+	} while (c == sc_None);
+	do
+	{
+		IN_ReadCursor(&cursorinfo);
+	} while (cursorinfo.button0 || cursorinfo.button1);
+
+	IN_ClearKeysDown();
+	USL_DrawCtlPanel();
+	return(c == sc_Y);
+}
+
+static boolean
+USL_ConfirmComm(UComm comm)
+{
+	boolean confirm,dialog;
+	char    *s1,*s2,*s3;
+
+	if (!comm)
+		Quit("USL_ConfirmComm() - empty comm");
+
+	confirm = true;
+	dialog = false;
+	s3 = "ESC TO BACK OUT";
+	switch (comm)
+	{
+	case uc_Abort:
+		s1 = "REALLY END CURRENT GAME?";
+		s2 = "PRESS Y TO END IT";
+		if (ingame && GameIsDirty)
+			dialog = true;
+		break;
+	case uc_Quit:
+		s1 = "REALLY QUIT?";
+		s2 = "PRESS Y TO QUIT";
+		dialog = true;
+		break;
+	case uc_Loaded:
+		s1 = "YOU'RE IN A GAME";
+		s2 = "PRESS Y TO LOAD GAME";
+		if (ingame && GameIsDirty)
+			dialog = true;
+		break;
+	case uc_SEasy:
+	case uc_SNormal:
+	case uc_SHard:
+		s1 = "YOU'RE IN A GAME";
+		s2 = "PRESS Y FOR NEW GAME";
+		if (ingame && GameIsDirty)
+			dialog = true;
+		break;
+	}
+
+	confirm = dialog? USL_CtlDialog(s1,s2,s3) : true;
+	if (confirm)
+	{
+		Communication = comm;
+		CtlPanelDone = true;
+	}
+	return(confirm);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      USL_HandleError() - Handles telling the user that there's been an error
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+USL_HandleError(int num)
+{
+	char    buf[64];
+
+	strcpy(buf,"Error: ");
+	if (num < 0)
+		strcat(buf,"Unknown");
+	else if (num == ENOMEM)
+		strcat(buf,"Disk is Full");
+	else if (num == EINVFMT)
+		strcat(buf,"File is Incomplete");
+	else
+		strcat(buf,sys_errlist[num]);
+
+	VW_HideCursor();
+
+	USL_CtlDialog(buf,"PRESS ANY KEY",nil);
+	VW_UpdateScreen();
+
+	IN_ClearKeysDown();
+	IN_Ack();
+
+	VW_ShowCursor();
+	VW_UpdateScreen();
+}
+
+//      Custom routines
+#if 0
+static boolean
+USL_GenericCustom(UserCall call,UserItem far *item)
+{
+	boolean result;
+
+	result = false;
+	switch (call)
+	{
+	}
+	return(result);
+}
+#endif
+
+static void
+USL_SetOptionsText(void)
+{
+	optionsi[0].text = showscorebox? "SCORE BOX (ON)" : "SCORE BOX (OFF)";
+	optionsi[1].text = oldshooting? "TWO-BUTTON FIRING (ON)" : "TWO-BUTTON FIRING (OFF)";
+#if GRMODE != CGAGR
+	optionsi[2].text = jerk? "FIX JERKY MOTION (ON)" : "FIX JERKY MOTION (OFF)";
+	optionsi[3].text = compatability? "SVGA COMPATIBILITY (ON)" : "SVGA COMPATIBILITY (OFF)";
+#endif
+
+	keybi[2].flags &= ~ui_Disabled;
+	if (oldshooting)
+		keybi[2].flags |= ui_Disabled;
+
+	// gravis option is only enabled when a joystick is selected
+	configi[6].flags |= ui_Disabled;
+	if (Controls[0] == ctrl_Joystick1 || Controls[0] == ctrl_Joystick2)
+		configi[6].flags &= ~ui_Disabled;
+
+	configi[6].text = GravisGamepad? "USE GRAVIS GAMEPAD (ON)" : "USE GRAVIS GAMEPAD (OFF)";
+}
+
+#pragma argsused
+static boolean
+USL_ScoreCustom(UserCall call,UserItem far *item)
+{
+	if (call != uic_SetupCard)
+		return(false);
+
+	showscorebox ^= true;
+	USL_CtlDialog(showscorebox? "Score box now on" : "Score box now off",
+					"Press any key",nil);
+	USL_SetOptionsText();
+	return(true);
+}
+
+#pragma argsused
+static boolean
+USL_SmoothCustom(UserCall call,UserItem far *item)
+{
+	if (call != uic_SetupCard)
+		return(false);
+
+	jerk ^= true;
+	USL_CtlDialog(jerk? "Jerky motion fix enabled" : "Jerky motion fix disabled",
+					"Press any key",nil);
+	USL_SetOptionsText();
+	return(true);
+}
+
+#pragma argsused
+static boolean
+USL_CompCustom(UserCall call,UserItem far *item)
+{
+	if (call != uic_SetupCard)
+		return(false);
+
+	compatability ^= true;
+	USL_CtlDialog(compatability? "SVGA compatibility now on" : "SVGA compatibility now off",
+					"Press any key",nil);
+	USL_SetOptionsText();
+	return(true);
+}
+
+#ifdef  KEEN
+#pragma argsused
+static boolean
+USL_TwoCustom(UserCall call,UserItem far *item)
+{
+	if (call != uic_SetupCard)
+		return(false);
+
+	oldshooting ^= true;
+	USL_CtlDialog(oldshooting? "Two-button firing now on" : "Two-button firing now off",
+					"Press any key",nil);
+	USL_SetOptionsText();
+	return(true);
+}
+#endif
+
+static boolean
+USL_ConfigCustom(UserCall call,UserItem far *item)
+{
+static  char    *CtlNames[] = {"KEYBOARD","KEYBOARD","JOYSTICK #1","JOYSTICK #2","MOUSE"};
+		char    *s;
+		word    w,h,
+				tw;
+
+	if (call == uic_TouchupCard)
+	{
+		s = "CONTROL: ";
+		USL_MeasureString(s,&w,&h);
+		tw = w;
+		USL_MeasureString(CtlNames[Controls[0]],&w,&h);
+		tw += w;
+		py = CtlPanelEY - 18 - h;
+		px = CtlPanelSX + ((CtlPanelW - tw) / 2);
+		fontcolor = NohiliteColor;
+		USL_DrawString(s);
+		USL_DrawString(CtlNames[Controls[0]]);
+	}
+	item++; // Shut the compiler up
+	return(false);
+}
+
+static void
+USL_CKSetKey(UserItem far *item,word i)
+{
+	boolean         on;
+	word            j;
+	ScanCode        scan;
+	longword        time;
+	CursorInfo      cursorinfo;
+
+	on = false;
+	time = 0;
+	LastScan = sc_None;
+	fontcolor = HiliteColor;
+	do
+	{
+		if (TimeCount >= time)
+		{
+			on ^= true;
+			VWB_Bar(item->x + 90,item->y,40,8,fontcolor ^ BackColor);
+			VWB_Bar(item->x + 90 + 1,item->y + 1,40 - 2,8 - 2,BackColor);
+			if (on)
+				VWB_DrawTile8(item->x + 90 + 16,item->y,TileBase + 8);
+			VW_UpdateScreen();
+
+			time = TimeCount + (TickBase / 2);
+		}
+
+		IN_ReadCursor(&cursorinfo);
+		while (cursorinfo.button0 || cursorinfo.button1)
+		{
+			IN_ReadCursor(&cursorinfo);
+			LastScan = sc_Escape;
+		}
+
+	asm     pushf
+	asm     cli
+		if (LastScan == sc_LShift)
+			LastScan = sc_None;
+	asm     popf
+	} while (!(scan = LastScan));
+
+	if (scan != sc_Escape)
+	{
+		for (j = 0,on = false;j < 11;j++)
+		{
+			if (j == i)
+				continue;
+			if (*(KeyMaps[j]) == scan)
+			{
+				on = true;
+				break;
+			}
+		}
+		if (on)
+#ifdef KEEN
+			USL_CtlDialog("Key already used","Press any key",nil);
+#else
+			USL_CtlDialog("Key already used","Press a key",nil);
+#endif
+		else
+			*(KeyMaps[i]) = scan;
+	}
+	IN_ClearKeysDown();
+}
+
+#pragma argsused
+static boolean
+USL_KeySCustom(UserCall call,UserItem far *item)
+{
+	if (call == uic_SetupCard)
+	{
+		Controls[0] = ctrl_Keyboard;
+		GravisGamepad = false;
+		USL_SetOptionsText();
+	}
+	return(false);
+}
+
+#pragma argsused
+static boolean
+USL_KeyCustom(UserCall call,UserItem far *item)
+{
+	boolean result;
+	word    i;
+
+	result = false;
+	i = (topcard == &keygroup)? (3 + (item - keyi)) : (item - keybi);
+	switch (call)
+	{
+	case uic_SetupCard:
+		Controls[0] = ctrl_Keyboard;
+		break;
+	case uic_Draw:
+		VWB_Bar(CtlPanelSX + 1,item->y,
+				CtlPanelEX - CtlPanelSX - 1,8,BackColor);       // Clear out background
+		USL_DrawItemIcon(item);
+		fontcolor = (item->flags & ui_Selected)? HiliteColor : NohiliteColor;
+		px = item->x + 8;
+		py = item->y + 1;
+		USL_DrawString(item->text);
+		VWB_Bar(item->x + 90,item->y,40,8,fontcolor ^ BackColor);
+		VWB_Bar(item->x + 90 + 1,item->y + 1,40 - 2,8 - 2,BackColor);
+		px = item->x + 90 + 6;
+		py = item->y + 1;
+		USL_DrawString(IN_GetScanName(*KeyMaps[i]));
+		result = true;
+		break;
+	case uic_Hit:
+		USL_KeyCustom(uic_Draw,item);
+		USL_CKSetKey(item,i);
+		USL_DrawCtlPanel();
+		result = true;
+		break;
+	}
+	return(result);
+}
+
+static void
+USL_CJDraw(char *s1,char *s2)
+{
+	word    w,h;
+
+	USL_MeasureString(s1,&w,&h);
+	px = CtlPanelSX + ((CtlPanelW - w) / 2);
+	py = CtlPanelEY - 34;
+	VWB_Bar(CtlPanelSX + 1,py,CtlPanelW - 2,h * 2,BackColor);
+	fontcolor = HiliteColor;
+	USL_DrawString(s1);
+	py += h;
+	USL_MeasureString(s2,&w,&h);
+	px = CtlPanelSX + ((CtlPanelW - w) / 2);
+	USL_DrawString(s2);
+}
+
+static boolean
+USL_CJGet(word joy,word button,word x,word y,word *xaxis,word *yaxis)
+{
+	boolean         on;
+	longword        time;
+
+	while (IN_GetJoyButtonsDB(joy))
+		if (LastScan == sc_Escape)
+			return(false);
+
+	on = false;
+	time = 0;
+	while (!(IN_GetJoyButtonsDB(joy) & (1 << button)))
+	{
+		if (TimeCount >= time)
+		{
+			on ^= true;
+			time = TimeCount + (TickBase / 2);
+			VWB_DrawTile8(x,y,TileBase + on);
+			VW_UpdateScreen();
+		}
+
+		if (LastScan == sc_Escape)
+			return(false);
+	}
+	IN_GetJoyAbs(joy,xaxis,yaxis);
+	return(true);
+}
+
+static boolean
+USL_ConfigJoystick(word joy)
+{
+	word    x,y,
+			minx,miny,
+			maxx,maxy;
+
+	BottomS1 = BottomS2 = "";
+#ifdef KEEN
+	BottomS3 = "ESC to back out";
+#else
+	BottomS3 = "Esc to back out";
+#endif
+	USL_DrawCtlPanel();
+	x = CtlPanelSX + 60;
+	y = CtlPanelSY + 19;
+	VWB_DrawPic(x,y,CP_JOYSTICKPIC);
+
+	USL_CJDraw("Move Joystick to upper left","and press button #1");
+	VWB_DrawTile8(x + 24,y + 8,TileBase + 6);
+	VWB_DrawTile8(x + 8,y + 8,TileBase + 1);
+	VWB_DrawTile8(x + 8,y + 24,TileBase + 0);
+	VW_UpdateScreen();
+	if (!USL_CJGet(joy,0,x + 8,y + 8,&minx,&miny))
+		return(false);
+
+	USL_CJDraw("Move Joystick to lower right","and press button #2");
+	VWB_DrawTile8(x + 24,y + 8,TileBase - 25);
+	VWB_DrawTile8(x + 40,y + 24,TileBase + 7);
+	VWB_DrawTile8(x + 8,y + 8,TileBase + 0);
+	VWB_DrawTile8(x + 8,y + 24,TileBase + 1);
+	VW_UpdateScreen();
+	if (!USL_CJGet(joy,1,x + 8,y + 24,&maxx,&maxy))
+		return(false);
+
+	while (IN_GetJoyButtonsDB(joy))
+		;
+
+#ifdef KEEN
+	if (minx != maxx && miny != maxy)
+	{
+		IN_SetupJoy(joy,minx,maxx,miny,maxy);
+		return(true);
+	}
+	return(false);
+#else
+	IN_SetupJoy(joy,minx,maxx,miny,maxy);
+	return(true);
+#endif
+}
+
+#pragma argsused
+static boolean
+USL_Joy1Custom(UserCall call,UserItem far *item)
+{
+	if (call == uic_SetupCard)
+	{
+		if (USL_ConfigJoystick(0))
+		{
+			Controls[0] = ctrl_Joystick1;
+			USL_CtlDialog("USING JOYSTICK #1","PRESS ANY KEY",nil);
+			USL_SetOptionsText();
+		}
+		return(true);
+	}
+	else
+		return(false);
+}
+
+#pragma argsused
+static boolean
+USL_Joy2Custom(UserCall call,UserItem far *item)
+{
+	if (call == uic_SetupCard)
+	{
+		if (USL_ConfigJoystick(1))
+		{
+			Controls[0] = ctrl_Joystick2;
+			USL_CtlDialog("USING JOYSTICK #2","PRESS ANY KEY",nil);
+			USL_SetOptionsText();
+		}
+		return(true);
+	}
+	else
+		return(false);
+}
+
+static void
+USL_CGDraw(char *s1, char *s2, int buttonsDone)
+{
+	static char *GButtonNames[4] = {"Red","Blue","Yellow","Green"};
+	static char *GActionNames[4] = {"Jump","Pogo","Fire","Status"};
+
+	int	i, n;
+	char	*actionstr;
+	word	w, h;
+
+	VWB_Bar(CtlPanelSX+1, CtlPanelSY+16, CtlPanelW-2, 68, BackColor);
+	px = CtlPanelSX+8;
+	py = CtlPanelSY+16;
+	USL_DrawString("Make sure that the button");
+	px = CtlPanelSX+8;
+	py = CtlPanelSY+24;
+	USL_DrawString("switch is set for 4 buttons");
+
+	for (i=0; i<4; i++)
+	{
+		px = CtlPanelSX+8;
+		py = i*8 + CtlPanelSY+40;
+		USL_DrawString(GButtonNames[i]);
+		USL_DrawString(":");
+		actionstr = "?";
+		for (n=0;n<buttonsDone;n++)
+		{
+			if (GravisMap[n] == i)
+				actionstr = GActionNames[n];
+		}
+		px = CtlPanelSX+56;
+		USL_DrawString(actionstr);
+	}
+
+	USL_MeasureString(s1, &w, &h);
+	px = w;
+	USL_MeasureString(s2, &w, &h);
+	px = (CtlPanelW-px-w)/2 + CtlPanelSX;
+	py = CtlPanelSY+76;
+	USL_DrawString(s1);
+	USL_DrawString(s2);
+	VW_UpdateScreen();
+}
+
+static boolean
+USL_CGGet(int buttonsDone, char *action)
+{
+	word	buttons, i, n;
+
+	USL_CGDraw("PRESS BUTTON FOR ", action, buttonsDone);
+
+redo:
+	do
+	{
+		if (LastScan == sc_Escape)
+		{
+			Keyboard[sc_Escape] = false;
+			if (LastScan == sc_Escape)
+				LastScan = sc_None;
+			return false;
+		}
+
+		buttons = IN_GetJoyButtonsDB(2);
+		if (!buttons)
+			continue;
+
+		for(i=n=0; i<4; i++)
+		{
+			if (buttons & (1 << i))
+				n += i+1;
+		}
+
+		if (!n || n >= 5)
+			continue;
+
+		n--;
+		for (i=0; i<buttonsDone; i++)
+		{
+			if (GravisMap[i] == n)
+				goto redo;
+		}
+
+		GravisMap[buttonsDone] = n;
+		return true;
+	} while (true);
+}
+
+#pragma argsused
+static boolean
+USL_JoyGCustom(UserCall call,UserItem far *item)
+{
+	if (call == uic_SetupCard)
+	{
+		if (GravisGamepad)
+		{
+			GravisGamepad = false;
+		}
+		else
+		{
+			BottomS1 = BottomS2 = "";
+			BottomS3 = "ESC to back out";
+			USL_DrawCtlPanel();
+			fontcolor = HiliteColor;
+			px = CtlPanelSX + 8;
+			py = CtlPanelSX + 8;
+			fontcolor = HiliteColor;	// redundant...
+			IN_ClearKeysDown();
+			if (  USL_CGGet(0, "JUMP")
+				&& USL_CGGet(1, "POGO")
+				&& USL_CGGet(2, "FIRE")
+				&& USL_CGGet(3, "STATUS") )
+			{
+				GravisGamepad = true;
+				USL_CGDraw("PRESS ANY KEY", "", 4);
+				IN_Ack();
+			}
+			else
+			{
+				GravisGamepad = false;
+			}
+		}
+		USL_SetOptionsText();
+		return true;
+	}
+	return false;
+}
+
+static void
+USL_DrawFileIcon(UserItem far *item)
+{
+	word    color;
+
+	item->y = topcard->y + CtlPanelSY + 12;
+	item->y += (item - loadsavegamei) * 11;
+
+	fontcolor = (item->flags & ui_Selected)? HiliteColor : NohiliteColor;
+	color = fontcolor ^ BackColor;  // Blech!
+	VWB_Hlin(item->x,item->x + (CtlPanelW - 12),item->y,color);
+	VWB_Hlin(item->x,item->x + (CtlPanelW - 12),item->y + 9,color);
+	VWB_Vlin(item->y,item->y + 9,item->x,color);
+	VWB_Vlin(item->y,item->y + 9,item->x + (CtlPanelW - 12),color);
+}
+
+static void
+USL_DoLoadGame(UserItem far *item)
+{
+	char            *filename;
+	word            n,
+				err;
+	int                     file;
+	SaveGame        *game;
+
+	if (!USL_ConfirmComm(uc_Loaded))
+		return;
+
+	n = item - loadsavegamei;
+	game = &Games[n];
+
+	USL_ShowLoadSave("Loading",game->name);
+
+	err = 0;
+	filename = USL_GiveSaveName(n);
+	if ((file = open(filename,O_BINARY | O_RDONLY)) != -1)
+	{
+		if (read(file,game,sizeof(*game)) == sizeof(*game))
+		{
+			if (USL_LoadGame)
+				if (!USL_LoadGame(file))
+					USL_HandleError(err = errno);
+		}
+		else
+			USL_HandleError(err = errno);
+		close(file);
+	}
+	else
+		USL_HandleError(err = errno);
+	if (err)
+	{
+		abortgame = true;
+		Communication = uc_None;
+		CtlPanelDone = false;
+	}
+	else
+		loadedgame = true;
+	game->present = true;
+
+	if (loadedgame)
+		Paused = true;
+
+	USL_DrawCtlPanel();
+}
+
+static boolean
+USL_LoadCustom(UserCall call,UserItem far *item)
+{
+	boolean result;
+	word    i;
+
+	result = false;
+	switch (call)
+	{
+	case uic_SetupCard:
+#ifdef KEEN
+		if (getenv("UID"))
+			USL_CheckSavedGames();
+#endif
+		for (i = 0;i < MaxSaveGames;i++)
+		{
+			if (Games[i].present)
+				loadsavegamei[i].flags &= ~ui_Disabled;
+			else
+				loadsavegamei[i].flags |= ui_Disabled;
+		}
+		break;
+	case uic_DrawIcon:
+		USL_DrawFileIcon(item);
+		result = true;
+		break;
+	case uic_Draw:
+		USL_DrawFileIcon(item);
+		VWB_Bar(item->x + 1,item->y + 2,CtlPanelW - 12 - 2,7,BackColor);
+
+		i = item - loadsavegamei;
+		if (Games[i].present)
+			px = item->x + 2;
+		else
+			px = item->x + 60;
+		py = item->y + 2;
+		USL_DrawString(Games[i].present? Games[i].name : "Empty");
+		result = true;
+		break;
+	case uic_Hit:
+		USL_DoLoadGame(item);
+		result = true;
+		break;
+	}
+	return(result);
+}
+
+static void
+USL_DoSaveGame(UserItem far *item)
+{
+	boolean         ok;
+	char            *filename;
+	word            n,err;
+	int         file;
+	SaveGame        *game;
+
+	BottomS1 = "Type name";
+	BottomS2 = "Enter accepts";
+	USL_DrawCtlPanel();
+
+	n = item - loadsavegamei;
+	game = &Games[n];
+	fontcolor = HiliteColor;
+	VWB_Bar(item->x + 1,item->y + 2,CtlPanelW - 12 - 2,7,BackColor);
+	game->oldtest = &PrintX;
+	ok = US_LineInput(item->x + 2,item->y + 2,
+						game->name,game->present? game->name : nil,
+						true,MaxGameName,
+						CtlPanelW - 22);
+	if (!strlen(game->name))
+		strcpy(game->name,"Untitled");
+	if (ok)
+	{
+		USL_ShowLoadSave("Saving",game->name);
+
+		filename = USL_GiveSaveName(n);
+		err = 0;
+		file = open(filename,O_CREAT | O_BINARY | O_WRONLY,
+					S_IREAD | S_IWRITE | S_IFREG);
+		if (file != -1)
+		{
+			if (write(file,game,sizeof(*game)) == sizeof(*game))
+			{
+				if (USL_SaveGame)
+					ok = USL_SaveGame(file);
+				if (!ok)
+					USL_HandleError(err = errno);
+			}
+			else
+				USL_HandleError(err = ((errno == ENOENT)? ENOMEM : errno));
+			close(file);
+		}
+		else
+			USL_HandleError(err = ((errno == ENOENT)? ENOMEM : errno));
+		if (err)
+		{
+			remove(filename);
+			ok = false;
+		}
+
+	}
+
+	if (!game->present)
+		game->present = ok;
+
+	if (ok)
+		GameIsDirty = false;
+	USL_SetupCard();
+}
+
+static boolean
+USL_SaveCustom(UserCall call,UserItem far *item)
+{
+	word    i;
+
+	switch (call)
+	{
+	case uic_SetupCard:
+#ifdef KEEN
+		if (getenv("UID"))
+			USL_CheckSavedGames();
+#endif
+		for (i = 0;i < MaxSaveGames;i++)
+			loadsavegamei[i].flags &= ~ui_Disabled;
+		return(false);
+	case uic_Hit:
+		USL_DoSaveGame(item);
+		return(true);
+//              break;
+	}
+	return(USL_LoadCustom(call,item));
+}
+
+#define PaddleMinX      (CtlPanelSX + 4)
+#define PaddleMaxX      (CtlPanelEX - 15)
+#define BallMinX        (CtlPanelSX + 4)
+#define BallMinY        (CtlPanelSY + 12 + 2)
+#define BallMaxX        (CtlPanelEX - 6)
+#define BallMaxY        (CtlPanelEY - 13)
+#define CPaddleY        (BallMinY + 4)
+#define KPaddleY        (BallMaxY - 2)
+void
+USL_DrawPongScore(word k,word c)
+{
+	fontcolor = HiliteColor;
+	PrintY = py = CtlPanelSY + 4;
+	px = CtlPanelSX + 6;
+	VWB_Bar(px,py,42,6,BackColor);
+	USL_DrawString("KEEN:");
+	PrintX = px;
+	US_PrintUnsigned(k);
+	px = CtlPanelSX + 108;
+	VWB_Bar(px,py,50,6,BackColor);
+	USL_DrawString("COMP:");
+	PrintX = px;
+	US_PrintUnsigned(c);
+}
+
+void
+USL_PlayPong(void)
+{
+	boolean         ball,killball,revdir,done,lastscore;
+	word            cycle,
+				x,y,
+				kx,cx,
+				rx,
+				bx,by,
+				oldkx,oldcx,oldbx,oldby,
+				kscore,cscore,
+				speedup;
+	int                     bdx,bdy;
+	longword        balltime,lasttime,waittime;
+	CursorInfo      cursorinfo;
+
+	kx = cx = PaddleMinX + ((PaddleMaxX - PaddleMinX) / 2);
+	bx = by = bdx = bdy = 0;
+	oldbx = oldcx = oldkx = PaddleMinX;
+	oldby = BallMinY;
+	kscore = cscore = 0;
+	USL_DrawPongScore(0,0);
+	cycle = 0;
+	revdir = false;
+	killball = true;
+	done = false;
+	lastscore = false;
+	lasttime = TimeCount;
+	do
+	{
+		while ((waittime = TimeCount - lasttime) == 0)
+			;
+
+		lasttime = TimeCount;
+		if (waittime > 4)
+			waittime = 4;
+
+		while (waittime-- && !done && LastScan != sc_Escape)
+		{
+			IN_ReadCursor(&cursorinfo);
+			if (((cursorinfo.x < 0) || IN_KeyDown(sc_LeftArrow)) && (kx > PaddleMinX))
+				kx -= 2;
+			else if (((cursorinfo.x > 0) || IN_KeyDown(sc_RightArrow)) && (kx < PaddleMaxX))
+				kx += 2;
+
+			if (killball)
+			{
+				ball = false;
+				balltime = TickBase;
+				speedup = 10;
+				killball = false;
+				VWB_Bar(oldbx,oldby,5,5,BackColor);
+			}
+
+			if (ball && (cycle++ % 3))
+			{
+				x = (bx >> 2);
+				if (!(x & 1))
+					x += (US_RndT() & 1);
+
+				if ((cx + 6 < x) && (cx < PaddleMaxX))
+					cx += 1;
+				else if ((cx + 6 > x) && (cx > PaddleMinX))
+					cx -= 1;
+			}
+
+			if (!ball && !--balltime)
+			{
+				ball = true;
+				bdx = 1 - (US_RndT() % 3);
+				bdy = 3;
+				if (lastscore)
+					bdy = -bdy;
+				bx = (BallMinX + ((BallMaxX - BallMinX) / 2)) << 2;
+				by = (BallMinY + ((BallMaxY - BallMinY) / 2)) << 2;
+			}
+
+			if (ball)
+			{
+				if
+				(
+					(((bx + bdx) >> 2) > BallMaxX)
+				||      (((bx + bdx) >> 2) < BallMinX)
+				)
+				{
+					SD_PlaySound(BALLBOUNCESND);
+					bdx = -bdx;
+				}
+				bx += bdx;
+
+				if (((by + bdy) >> 2) > BallMaxY)
+				{
+					killball = true;
+					lastscore = false;
+					cscore++;
+					SD_PlaySound(COMPSCOREDSND);
+					USL_DrawPongScore(kscore,cscore);
+					if (cscore == 21)
+					{
+						USL_CtlDialog("You lost!","Press any key",nil);
+						done = true;
+						continue;
+					}
+				}
+				else if (((by + bdy) >> 2) < BallMinY)
+				{
+					killball = true;
+					lastscore = true;
+					kscore++;
+					SD_PlaySound(KEENSCOREDSND);
+					USL_DrawPongScore(kscore,cscore);
+					if (kscore == 21)
+					{
+						USL_CtlDialog("You won!","Press any key",nil);
+						done = true;
+						continue;
+					}
+				}
+				by += bdy;
+
+				x = bx >> 2;
+				y = by >> 2;
+				if (!killball)
+				{
+					if
+					(
+						(bdy < 0)
+					&&      ((y >= CPaddleY) && (y < CPaddleY + 3))
+					&&      ((x >= (cx - 5)) && (x < (cx + 11)))
+					)
+					{
+						rx = cx;
+						revdir = true;
+						SD_PlaySound(COMPPADDLESND);
+					}
+					else if
+					(
+						(bdy > 0)
+					&&      ((y >= (KPaddleY - 3)) && (y < KPaddleY))
+					&&      ((x >= (kx - 5)) && (x < (kx + 11)))
+					)
+					{
+						if (((bdy >> 2) < 3) && !(--speedup))
+						{
+							bdy++;
+							speedup = 10;
+						}
+						rx = kx;
+						revdir = true;
+						SD_PlaySound(KEENPADDLESND);
+					}
+					if (revdir)
+					{
+						bdy = -bdy;
+						bdx = ((x + 5 - rx) >> 1) - (1 << 2);
+						if (!bdx)
+							bdx--;
+						revdir = false;
+					}
+				}
+			}
+		}
+
+		if (ball)
+		{
+			VWB_Bar(oldbx,oldby,5,5,BackColor);
+			oldbx = x;
+			oldby = y;
+#if GRMODE == CGAGR
+			{
+				static int ballsprites[4] = {BALLSPR, BALL1PIXELTOTHERIGHTSPR, BALL2PIXELSTOTHERIGHTSPR, BALL3PIXELSTOTHERIGHTSPR};
+				VWB_DrawSprite(x,y,ballsprites[x & 3]);
+			}
+#else
+			VWB_DrawSprite(x,y,(x & 1)? BALL1PIXELTOTHERIGHTSPR : BALLSPR);
+#endif
+		}
+		VWB_Bar(oldcx-3,CPaddleY,16,3,BackColor);
+		oldcx = cx;
+		VWB_DrawSprite(cx,CPaddleY,PADDLESPR);
+		VWB_Bar(oldkx-3,KPaddleY,16,3,BackColor);
+		oldkx = kx;
+		VWB_DrawSprite(kx,KPaddleY,PADDLESPR);
+
+		VW_UpdateScreen();
+	} while ((LastScan != sc_Escape) && !done);
+	IN_ClearKeysDown();
+}
+
+#pragma argsused
+static boolean
+USL_PongCustom(UserCall call,struct UserItem far *item)
+{
+	if (call != uic_SetupCard)
+		return(false);
+
+	VWB_DrawPic(0,0,CP_MENUSCREENPIC);
+	VWB_DrawPic(CtlPanelSX + 56,CtlPanelSY,CP_PADDLEWARPIC);
+	VWB_Hlin(CtlPanelSX + 3,CtlPanelEX - 3,CtlPanelSY + 12,HiliteColor ^ BackColor);
+	VWB_Hlin(CtlPanelSX + 3,CtlPanelEX - 3,CtlPanelEY - 7,HiliteColor ^ BackColor);
+	USL_PlayPong();
+
+	return(true);
+}
+
+//      Flag management stuff
+static void
+USL_ClearFlags(UserItemGroup far *node)
+{
+	UserItem        far *i;
+
+	if (!node->items)
+		return;
+
+	for (i = node->items;i->type != uii_Bad;i++)
+	{
+		i->flags &= ~UISelectFlags;
+		if (i->child)
+			USL_ClearFlags((UserItemGroup far *)i->child);
+	}
+}
+
+static int
+USL_FindPushedItem(UserItemGroup far *group)
+{
+	word            i;
+	UserItem        far *item;
+
+	for (item = group->items,i = 0;item->type != uii_Bad;item++,i++)
+		if (item->flags & ui_Pushed)
+			return(i);
+	return(-1);
+}
+
+static void
+USL_SelectItem(UserItemGroup far *group,word index,boolean draw)
+{
+	UserItem        far *item;
+
+	if (index != group->cursor)
+	{
+		item = &group->items[group->cursor];
+		item->flags &= ~ui_Selected;
+		if (draw)
+			USL_DrawItem(item);
+	}
+
+	group->cursor = index;
+	item = &group->items[group->cursor];
+	group->items[group->cursor].flags |= ui_Selected;
+	if (draw)
+		USL_DrawItem(item);
+}
+
+static void
+USL_PushItem(UserItemGroup far *group,word index,boolean draw)
+{
+	word            i;
+	UserItem        far *item;
+
+	USL_SelectItem(group,index,draw);
+	for (item = group->items,i = 0;item->type != uii_Bad;item++,i++)
+	{
+		if (item->type != uii_RadioButton)
+			continue;
+
+		if (i == index)
+		{
+			item->flags |= ui_Pushed;
+			if (draw)
+				USL_DrawItem(item);
+		}
+		else if (item->flags & ui_Pushed)
+		{
+			item->flags &= ~ui_Pushed;
+			if (draw)
+				USL_DrawItem(item);
+		}
+	}
+}
+
+static void
+USL_NextItem(void)
+{
+	if (topcard->items[topcard->cursor + 1].type == uii_Bad)
+		return;
+	USL_SelectItem(topcard,topcard->cursor + 1,true);
+}
+
+static void
+USL_PrevItem(void)
+{
+	if (!topcard->cursor)
+		return;
+	USL_SelectItem(topcard,topcard->cursor - 1,true);
+}
+
+static void
+USL_SetupCard(void)
+{
+	BottomS1 = "Arrows move";
+	BottomS2 = "Enter selects";
+	BottomS3 = cstackptr? "ESC to back out" : "ESC to quit";
+
+	USL_SelectItem(topcard,topcard->cursor,false);
+	USL_DrawCtlPanel();     // Contents?
+}
+
+static void
+USL_DownLevel(UserItemGroup far *group)
+{
+	if (!group)
+		Quit("USL_DownLevel() - nil card");
+	USL_PushCard(group);
+	if (group->custom && group->custom(uic_SetupCard,nil))
+		USL_PopCard();
+	USL_SetupCard();
+}
+
+static void
+USL_UpLevel(void)
+{
+	if (!cstackptr)
+	{
+		USL_ConfirmComm(uc_Quit);
+		return;
+	}
+
+	if (topcard->items)
+		topcard->items[topcard->cursor].flags &= ~ui_Selected;
+	USL_PopCard();
+	USL_SetupCard();
+}
+
+static void
+USL_DoItem(void)
+{
+	// DEBUG - finish this routine
+	UserItem                far *item;
+
+	item = &topcard->items[topcard->cursor];
+	if (item->flags & ui_Disabled)
+		SD_PlaySound(NOWAYSND);
+	else
+	{
+		switch (item->type)
+		{
+		case uii_Button:
+			if (!(topcard->custom && topcard->custom(uic_Hit,item)))
+				USL_ConfirmComm(item->comm);
+			break;
+		case uii_RadioButton:
+			USL_PushItem(topcard,topcard->cursor,true);
+			break;
+		case uii_Folder:
+			USL_DownLevel(item->child);
+			break;
+		}
+	}
+}
+
+static void
+USL_SetControlValues(void)
+{
+	int sndindex;
+
+	sndindex = SoundMode;
+	if (sndindex == sdm_AdLib && QuietFX)
+		sndindex++;
+
+	USL_PushItem(&soundgroup,sndindex,false);
+	USL_PushItem(&musicgroup,MusicMode,false);
+	if (!AdLibPresent)
+	{
+		soundi[2].flags |= ui_Disabled; // AdLib sound effects
+		soundi[3].flags |= ui_Disabled; // Quiet AdLib sound effects
+		musici[1].flags |= ui_Disabled; // AdLib music
+	}
+
+#ifdef CAT3D
+	if (!JoysPresent[0])
+		configi[3].flags |= ui_Disabled;
+	if (!JoysPresent[1])
+		configi[4].flags |= ui_Disabled;
+#else
+	if (!JoysPresent[0])
+		configi[4].flags |= ui_Disabled;
+	if (!JoysPresent[1])
+		configi[5].flags |= ui_Disabled;
+	if (!JoysPresent[0] && !JoysPresent[1])
+		configi[6].flags |= ui_Disabled;
+#endif
+
+	rooti[4].text = ingame? "RETURN TO GAME" : "RETURN TO DEMO";
+	if (!ingame)
+	{
+		rooti[2].flags |= ui_Disabled;  // Save Game
+		rooti[5].flags |= ui_Disabled;  // End Game
+	}
+	rootgroup.cursor = ingame? 4 : 0;
+	USL_SetOptionsText();
+	// DEBUG - write the rest of this
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      USL_SetUpCtlPanel() - Sets the states of the UserItems to reflect the
+//              values of all the appropriate variables
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+USL_SetUpCtlPanel(void)
+{
+	int     i;
+
+	// Cache in all of the stuff for the control panel
+	CA_UpLevel();
+	for (i = CONTROLS_LUMP_START;i <= CONTROLS_LUMP_END;i++)
+		CA_MarkGrChunk(i);
+	for (i = PADDLE_LUMP_START;i <= PADDLE_LUMP_END;i++)
+		CA_MarkGrChunk(i);
+	CA_MarkGrChunk(STARTFONT+1);            // Little font
+	CA_MarkGrChunk(CP_MENUMASKPICM);        // Mask for dialogs
+	CA_CacheMarks("Control Panel");
+	CA_LoadAllSounds();
+
+	// Do some other setup
+	fontnumber = 1;
+	US_SetPrintRoutines(VW_MeasurePropString,VWB_DrawPropString);
+	fontcolor = F_BLACK;
+#ifdef CAT3D
+	VW_Bar (0,0,320,200,3); // CAT3D patch
+#else
+	VW_ClearVideo(3);
+#endif
+	RF_FixOfs();
+	VW_InitDoubleBuffer();
+
+	Communication = uc_None;
+	USL_ClearFlags(&rootgroup);
+	USL_SetControlValues();
+	USL_SetupStack();
+	USL_SetupCard();
+
+	if (ingame)
+		GameIsDirty = true;
+
+	IN_ClearKeysDown();
+}
+
+static void
+USL_HandleComm(UComm comm)
+{
+	switch (comm)
+	{
+	case uc_Loaded:
+	case uc_Return:
+		break;
+	case uc_Abort:
+		abortgame = true;
+		break;
+	case uc_Quit:
+		QuitToDos = true;
+		break;
+	case uc_SEasy:
+		restartgame = gd_Easy;
+		break;
+	case uc_SNormal:
+		restartgame = gd_Normal;
+		break;
+	case uc_SHard:
+		restartgame = gd_Hard;
+		break;
+
+	default:
+		Quit("USL_HandleComm() - unknown");
+		break;
+	}
+}
+
+static void
+USL_GetControlValues(void)
+{
+	int     i;
+
+	// DEBUG - write the rest of this
+	i = USL_FindPushedItem(&soundgroup);
+	if (i == 3)
+	{
+		QuietFX = true;
+		i--;
+	}
+	else
+	{
+		QuietFX = false;
+	}
+	if (i != SoundMode)
+		SD_SetSoundMode(i);
+
+	i = USL_FindPushedItem(&musicgroup);
+	if (i != MusicMode)
+		SD_SetMusicMode(i);
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      USL_TearDownCtlPanel() - Given the state of the control panel, sets the
+//              modes and values as appropriate
+//
+///////////////////////////////////////////////////////////////////////////
+static void
+USL_TearDownCtlPanel(void)
+{
+	USL_GetControlValues();
+	if (Communication)
+		USL_HandleComm(Communication);
+
+	fontnumber = 0; // Normal font
+	fontcolor = F_BLACK;
+	if (restartgame && USL_ResetGame)
+		USL_ResetGame();
+	else if (QuitToDos)
+	{
+		if (tedlevel)
+			TEDDeath();
+		else
+		{
+			US_CenterWindow(20,3);
+			fontcolor = F_SECONDCOLOR;
+			US_PrintCentered("Quitting...");
+			fontcolor = F_BLACK;
+			VW_UpdateScreen();
+			Quit(nil);
+		}
+	}
+
+	IN_ClearKeysDown();
+	SD_WaitSoundDone();
+#ifdef CAT3D
+	VW_Bar (0,0,320,200,3); // CAT3D patch
+#else
+	VW_ClearVideo(3);
+#endif
+	CA_DownLevel();
+	CA_LoadAllSounds();
+}
+
+///////////////////////////////////////////////////////////////////////////
+//
+//      US_ControlPanel() - This is the main routine for the control panel
+//
+///////////////////////////////////////////////////////////////////////////
+#define MoveMin 40
+void
+US_ControlPanel(void)
+{
+extern void HelpScreens(void);
+
+	boolean         resetitem,on;
+	word            i;
+	int                     ydelta;
+	longword        flashtime;
+	UserItem        far *item;
+	CursorInfo      cursorinfo;
+
+#if 0
+	// DEBUG!!!
+	{
+		USL_SetUpCtlPanel();
+		Communication = uc_Loaded;
+		CtlPanelDone = true;
+		loadedgame = true;
+		USL_TearDownCtlPanel();
+		return;
+	}
+#endif
+
+	if ((LastScan < sc_F1) || (LastScan > sc_F10))
+		IN_ClearKeysDown();
+
+	USL_SetUpCtlPanel();
+	USL_DrawCtlPanel();
+
+	ydelta = 0;
+	for (CtlPanelDone = false,resetitem = on = true;!CtlPanelDone;)
+	{
+		item = &(topcard->items[topcard->cursor]);
+
+		if (resetitem)
+		{
+			flashtime = TimeCount + (TickBase / 2);
+			resetitem = false;
+		}
+
+		if (TimeCount >= flashtime)
+		{
+			on ^= true;
+			resetitem = true;
+			if (!on)
+				item->flags &= ~ui_Selected;
+			USL_DrawItemIcon(item);
+			item->flags |= ui_Selected;
+		}
+
+		VW_UpdateScreen();
+
+		if (LastScan)
+		{
+			switch (LastScan)
+			{
+			case sc_UpArrow:
+				USL_PrevItem();
+				resetitem = true;
+				break;
+			case sc_DownArrow:
+				USL_NextItem();
+				resetitem = true;
+				break;
+			case sc_Return:
+				USL_DoItem();
+				resetitem = true;
+				break;
+			case sc_Escape:
+				USL_UpLevel();
+				resetitem = true;
+				break;
+#ifndef KEEN6
+			case sc_F1:
+				HelpScreens();
+				USL_DrawCtlPanel();
+				resetitem = true;
+				break;
+#endif
+			}
+
+			if
+			(
+				(!resetitem)
+			&&      (
+					(LastScan == KbdDefs[0].button0)
+				||      (LastScan == KbdDefs[0].button1)
+				)
+			)
+			{
+				USL_DoItem();
+				resetitem = true;
+			}
+
+			if (!resetitem)
+			{
+				for (item = topcard->items,i = 0;item->type != uii_Bad;item++,i++)
+				{
+					if (item->hotkey == LastScan)
+					{
+						USL_SelectItem(topcard,i,true);
+						resetitem = true;
+						break;
+					}
+				}
+			}
+
+			IN_ClearKeysDown();
+		}
+		else
+		{
+			IN_ReadCursor(&cursorinfo);
+			ydelta += cursorinfo.y;
+			if (cursorinfo.button0)
+			{
+				do
+				{
+					IN_ReadCursor(&cursorinfo);
+				} while (cursorinfo.button0);
+				USL_DoItem();
+				resetitem = true;
+			}
+			else if (cursorinfo.button1)
+			{
+				do
+				{
+					IN_ReadCursor(&cursorinfo);
+				} while (cursorinfo.button1);
+				USL_UpLevel();
+				resetitem = true;
+			}
+			else if (ydelta < -MoveMin)
+			{
+				ydelta += MoveMin;
+				USL_PrevItem();
+				resetitem = true;
+			}
+			else if (ydelta > MoveMin)
+			{
+				ydelta -= MoveMin;
+				USL_NextItem();
+				resetitem = true;
+			}
+		}
+	}
+
+	USL_TearDownCtlPanel();
+}
+
+#ifdef KEEN6
+
+boolean US_ManualCheck(void)
+{
+	typedef struct {
+		char far *name;
+		int shapenum;
+		int x, y;
+	} creatureinfo;
+
+	static creatureinfo list[] = {
+		{"BIP",       BIPSHIPRSPR,        -2,  0},
+		{"BABOBBA",   BABOBBAR1SPR,        0,  0},
+		{"BLORB",     BLORB1SPR,          -2,  0},
+		{"GIK",       GIKWALKR1SPR,       -1,  0},
+		{"CEILICK",   CEILICK1SPR,         0,  0},
+		{"BLOOGLET",  RBLOOGLETWALKR1SPR, -2,  0},
+		{"BLOOGUARD", BLOOGUARDWALKL1SPR, -3, -1},
+		{"FLECT",     FLECTSTANDSPR,      -1,  0},
+		{"BOBBA",     BOBBAR1SPR,         -2,  0},
+		{"NOSPIKE",   NOSPIKESTANDSPR,    -2,  0},
+		{"ORBATRIX",  ORBATRIXR1SPR,      -2,  1},
+		{"FLEEX",     FLEEXWALKR1SPR,     -2,  0}
+	};
+
+	boolean correct;
+	char far *name;
+	char c;
+	char *ptr;
+	unsigned spriteheight, spritewidth;
+	int x, y;
+	int editwidth;
+	creatureinfo info;
+	char strbuf[16];
+
+	if (checkpassed)
+		return true;
+
+	correct = false;
+	if (listindex == -1)
+	{
+		_AH = 0x2C;	// get time
+		geninterrupt(0x21);
+		x = _CH;	// store hours
+		_AH = 0x2A;	// get date
+		geninterrupt(0x21);
+		y = _DL;	// store day
+
+		listindex = (x + y) % (int)(sizeof(list)/sizeof(creatureinfo));
+	}
+
+	CA_UpLevel();
+	info = list[listindex];
+	name = info.name;
+	CA_ClearMarks();
+	CA_MarkGrChunk(info.shapenum);
+	CA_CacheMarks(NULL);
+
+	VWB_Bar(0, 0, 320, 200, BackColor);
+	spritewidth = spritetable[info.shapenum - STARTSPRITES].width;
+	spriteheight = spritetable[info.shapenum - STARTSPRITES].height;
+	US_CenterWindow(30, (spriteheight+41)/8 + 1);
+	PrintY = WindowY + 2;
+	US_CPrint("What is the name of this creature?");
+
+	x = WindowX + (WindowW-spritewidth)/2 + info.x*8;
+	y = WindowY + 15;
+	if (info.shapenum == CEILICK1SPR)
+	{
+		y++;
+	}
+	else
+	{
+		y += info.y * 8;
+	}
+	VWB_DrawSprite(x, y, info.shapenum);
+
+	y = WindowY + WindowH - 16;
+	editwidth = 100;
+	x = WindowX + (WindowW - 100) / 2;
+	VWB_Bar(x, y, editwidth, 14, BLACK);
+	VWB_Bar(x+1, y+1, editwidth-2, 12, WHITE);
+	x += 2;
+	y += 2;
+	editwidth -= 8;
+	VW_UpdateScreen();
+
+	if (US_LineInput(x, y, strbuf, NULL, true, sizeof(strbuf), editwidth))
+	{
+		ptr = strbuf;
+		correct = true;
+		while (*name)
+		{
+			c = *ptr;
+			if ((islower(c)? _toupper(c) : c) != *name)
+			{
+				correct = false;
+			}
+
+			ptr++;
+			name++;
+		}
+		if (*ptr)
+		{
+			correct = false;
+		}
+
+		if (!correct)
+		{
+			VWB_Bar(0, 0, 320, 200, BackColor);
+			US_CenterWindow(35, 5);
+			PrintY += 11;
+			US_CPrint("Sorry, that's not quite right.");
+			US_CPrint("Please check your manual and try again.");
+			VW_UpdateScreen();
+			IN_Ack();
+		}
+	}
+
+	VWB_Bar(0, 0, 320, 200, BackColor);
+	CA_DownLevel();
+	checkpassed = correct;
+	return correct;
+}
+
+#endif
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/ID_US_A.ASM b/16/keen456/KEEN4-6/ID_US_A.ASM
new file mode 100755
index 00000000..15e6f12d
--- /dev/null
+++ b/16/keen456/KEEN4-6/ID_US_A.ASM
@@ -0,0 +1,117 @@
+; Catacomb 3-D Source Code
+; Copyright (C) 1993-2014 Flat Rock Software
+;
+; This program is free software; you can redistribute it and/or modify
+; it under the terms of the GNU General Public License as published by
+; the Free Software Foundation; either version 2 of the License, or
+; (at your option) any later version.
+;
+; This program is distributed in the hope that it will be useful,
+; but WITHOUT ANY WARRANTY; without even the implied warranty of
+; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+; GNU General Public License for more details.
+;
+; You should have received a copy of the GNU General Public License along
+; with this program; if not, write to the Free Software Foundation, Inc.,
+; 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+
+IDEAL
+MODEL	MEDIUM,C
+
+;	Assembly portion of the User Mgr. This is just John Carmack's table
+;		driven pseudo-random number generator, and we put it in the User Mgr
+;		because we couldn't figure out where it should go
+
+
+;============================================================================
+;
+;                           RANDOM ROUTINES
+;
+;============================================================================
+
+	FARDATA
+
+rndindex	dw	?
+
+rndtable db    0,   8, 109, 220, 222, 241, 149, 107,  75, 248, 254, 140,  16,  66
+	db   74,  21, 211,  47,  80, 242, 154,  27, 205, 128, 161,  89,  77,  36
+	db   95, 110,  85,  48, 212, 140, 211, 249,  22,  79, 200,  50,  28, 188
+	db   52, 140, 202, 120,  68, 145,  62,  70, 184, 190,  91, 197, 152, 224
+	db  149, 104,  25, 178, 252, 182, 202, 182, 141, 197,   4,  81, 181, 242
+	db  145,  42,  39, 227, 156, 198, 225, 193, 219,  93, 122, 175, 249,   0
+	db  175, 143,  70, 239,  46, 246, 163,  53, 163, 109, 168, 135,   2, 235
+	db   25,  92,  20, 145, 138,  77,  69, 166,  78, 176, 173, 212, 166, 113
+	db   94, 161,  41,  50, 239,  49, 111, 164,  70,  60,   2,  37, 171,  75
+	db  136, 156,  11,  56,  42, 146, 138, 229,  73, 146,  77,  61,  98, 196
+	db  135, 106,  63, 197, 195,  86,  96, 203, 113, 101, 170, 247, 181, 113
+	db   80, 250, 108,   7, 255, 237, 129, 226,  79, 107, 112, 166, 103, 241
+	db   24, 223, 239, 120, 198,  58,  60,  82, 128,   3, 184,  66, 143, 224
+	db  145, 224,  81, 206, 163,  45,  63,  90, 168, 114,  59,  33, 159,  95
+	db   28, 139, 123,  98, 125, 196,  15,  70, 194, 253,  54,  14, 109, 226
+	db   71,  17, 161,  93, 186,  87, 244, 138,  20,  52, 123, 251,  26,  36
+	db   17,  46,  52, 231, 232,  76,  31, 221,  84,  37, 216, 165, 212, 106
+	db  197, 242,  98,  43,  39, 175, 254, 145, 190,  84, 118, 222, 187, 136
+	db  120, 163, 236, 249
+
+
+	CODESEG
+
+LastRnd		dw	?
+
+;=================================================
+;
+; void US_InitRndT (boolean randomize)
+; Init table based RND generator
+; if randomize is false, the counter is set to 0
+;
+;=================================================
+
+PROC	US_InitRndT randomize:word
+	uses	si,di
+	public	US_InitRndT
+
+	mov	ax,SEG rndtable
+	mov	es,ax
+	mov	ax,[randomize]
+	or	ax,ax
+	jne	@@timeit		;if randomize is true, really random
+
+	mov	dx,0			;set to a definite value
+	jmp	@@setit
+
+@@timeit:
+	mov	ah,2ch
+	int	21h			;GetSystemTime
+	and	dx,0ffh
+
+@@setit:
+	mov	[es:rndindex],dx
+	ret
+
+ENDP
+
+;=================================================
+;
+; int US_RndT (void)
+; Return a random # between 0-255
+; Exit : AX = value
+;
+;=================================================
+PROC	US_RndT
+	public	US_RndT
+
+	mov	ax,SEG rndtable
+	mov	es,ax
+	mov	bx,[es:rndindex]
+	inc	bx
+	and	bx,0ffh
+	mov	[es:rndindex],bx
+	mov	al,[es:rndtable+BX]
+	xor	ah,ah
+
+	ret
+
+ENDP
+
+END
+
diff --git a/16/keen456/KEEN4-6/ID_VW.C b/16/keen456/KEEN4-6/ID_VW.C
new file mode 100755
index 00000000..69b54c5c
--- /dev/null
+++ b/16/keen456/KEEN4-6/ID_VW.C
@@ -0,0 +1,1548 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+// ID_VW.C
+
+#include "ID_HEADS.H"
+
+/*
+=============================================================================
+
+						 LOCAL CONSTANTS
+
+=============================================================================
+*/
+
+#define VIEWWIDTH		40
+
+#define PIXTOBLOCK		4		// 16 pixels to an update block
+
+/*
+=============================================================================
+
+						 GLOBAL VARIABLES
+
+=============================================================================
+*/
+
+cardtype	videocard;		// set by VW_Startup
+grtype		grmode;			// CGAgr, EGAgr, VGAgr
+
+unsigned	bufferofs;		// hidden area to draw to before displaying
+unsigned	displayofs;		// origin of the visable screen
+unsigned	panx,pany;		// panning adjustments inside port in pixels
+unsigned	pansx,pansy;	// panning adjustments inside port in screen
+							// block limited pixel values (ie 0/8 for ega x)
+unsigned	panadjust;		// panx/pany adjusted by screen resolution
+
+unsigned	screenseg;		// normally 0xa000 / 0xb800
+unsigned	linewidth;
+unsigned	ylookup[VIRTUALHEIGHT];
+
+unsigned	fontnumber;		// 0 based font number for drawing
+
+boolean		screenfaded;
+
+pictabletype	_seg *pictable;
+pictabletype	_seg *picmtable;
+spritetabletype _seg *spritetable;
+
+int			bordercolor;
+boolean			nopan;
+
+/*
+=============================================================================
+
+						 LOCAL VARIABLES
+
+=============================================================================
+*/
+
+void	VWL_MeasureString (char far *string, word *width, word *height,
+		fontstruct _seg *font);
+void 	VWL_DrawCursor (void);
+void 	VWL_EraseCursor (void);
+void 	VWL_DBSetup (void);
+void	VWL_UpdateScreenBlocks (void);
+
+
+int			bordercolor;
+int			cursorvisible;
+int			cursornumber,cursorwidth,cursorheight,cursorx,cursory;
+memptr		cursorsave;
+unsigned	cursorspot;
+
+//===========================================================================
+
+
+/*
+=======================
+=
+= VW_Startup
+=
+=======================
+*/
+
+static	char *ParmStrings[] = {"HIDDENCARD","NOPAN",""};
+
+void	VW_Startup (void)
+{
+	int i,n;
+
+	asm	cld;
+
+	videocard = 0;
+
+	for (i = 1;i < _argc;i++)
+	{
+		n = US_CheckParm(_argv[i],ParmStrings);
+		if (n == 0)
+		{
+			videocard = EGAcard;
+		}
+		else if (n == 1)
+		{
+			nopan = true;
+		}
+	}
+
+	if (!videocard)
+		videocard = VW_VideoID ();
+
+#if GRMODE == EGAGR
+	grmode = EGAGR;
+	if (videocard != EGAcard && videocard != VGAcard)
+#ifdef KEEN
+Quit ("Improper video card!  If you really have an EGA/VGA card that I am not\n"
+	  "detecting, use the -HIDDENCARD command line parameter!");
+#else
+Quit ("Improper video card!  If you really have an EGA/VGA card that I am not \n"
+	  "detecting, use the -HIDDENCARD command line parameter!");
+#endif
+	EGAWRITEMODE(0);
+#endif
+
+#if GRMODE == CGAGR
+	grmode = CGAGR;
+	if (videocard < CGAcard || videocard > VGAcard)
+#ifdef KEEN
+Quit ("Improper video card!  If you really have a CGA card that I am not\n"
+	  "detecting, use the -HIDDENCARD command line parameter!");
+#else
+Quit ("Improper video card!  If you really have a CGA card that I am not \n"
+	  "detecting, use the -HIDDENCARD command line parameter!");
+#endif
+	MM_GetPtr (&(memptr)screenseg,0x10000l);	// grab 64k for floating screen
+#endif
+
+	cursorvisible = 0;
+}
+
+//===========================================================================
+
+/*
+=======================
+=
+= VW_Shutdown
+=
+=======================
+*/
+
+void	VW_Shutdown (void)
+{
+	VW_SetScreenMode (TEXTGR);
+#if GRMODE == EGAGR
+	VW_SetLineWidth (80);
+#endif
+}
+
+//===========================================================================
+
+/*
+========================
+=
+= VW_SetScreenMode
+= Call BIOS to set TEXT / CGAgr / EGAgr / VGAgr
+=
+========================
+*/
+
+void VW_SetScreenMode (int grmode)
+{
+	switch (grmode)
+	{
+	  case TEXTGR:  _AX = 3;
+		  geninterrupt (0x10);
+#ifdef CAT3D
+		  screenseg=0xb000;
+#endif
+		  break;
+	  case CGAGR: _AX = 4;
+		  geninterrupt (0x10);		// screenseg is actually a main mem buffer
+		  break;
+	  case EGAGR: _AX = 0xd;
+		  geninterrupt (0x10);
+		  screenseg=0xa000;
+		  break;
+#ifdef VGAGAME
+	  case VGAGR:{
+		  char extern VGAPAL;	// deluxepaint vga pallet .OBJ file
+		  void far *vgapal = &VGAPAL;
+		  SetCool256 ();		// custom 256 color mode
+		  screenseg=0xa000;
+		  _ES = FP_SEG(vgapal);
+		  _DX = FP_OFF(vgapal);
+		  _BX = 0;
+		  _CX = 0x100;
+		  _AX = 0x1012;
+		  geninterrupt(0x10);			// set the deluxepaint pallet
+
+		  break;
+#endif
+	}
+	VW_SetLineWidth(SCREENWIDTH);
+}
+
+/*
+=============================================================================
+
+							SCREEN FADES
+
+=============================================================================
+*/
+
+char colors[7][17]=
+{{0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0},
+ {0,0,0,0,0,0,0,0,0,1,2,3,4,5,6,7,0},
+ {0,0,0,0,0,0,0,0,0x18,0x19,0x1a,0x1b,0x1c,0x1d,0x1e,0x1f,0},
+ {0,1,2,3,4,5,6,7,0x18,0x19,0x1a,0x1b,0x1c,0x1d,0x1e,0x1f,0},
+ {0,1,2,3,4,5,6,7,0x1f,0x1f,0x1f,0x1f,0x1f,0x1f,0x1f,0x1f,0},
+ {0x1f,0x1f,0x1f,0x1f,0x1f,0x1f,0x1f,0x1f,0x1f,0x1f,0x1f,0x1f,0x1f,0x1f,0x1f,0x1f,0x1f}};
+
+
+void VW_ColorBorder (int color)
+{
+	_AH=0x10;
+	_AL=1;
+	_BH=color;
+	geninterrupt (0x10);
+	bordercolor = color;
+}
+
+void VW_SetPalette(byte *palette)
+{
+	byte	p;
+	word	i;
+
+	for (i = 0;i < 15;i++)
+	{
+		p = palette[i];
+		colors[0][i] = 0;
+		colors[1][i] = (p > 0x10)? (p & 0x0f) : 0;
+		colors[2][i] = (p > 0x10)? p : 0;
+		colors[3][i] = p;
+		colors[4][i] = (p > 0x10)? 0x1f : p;
+		colors[5][i] = 0x1f;
+	}
+}
+
+void VW_SetDefaultColors(void)
+{
+#if GRMODE == EGAGR
+	colors[3][16] = bordercolor;
+	_ES=FP_SEG(&colors[3]);
+	_DX=FP_OFF(&colors[3]);
+	_AX=0x1002;
+	geninterrupt(0x10);
+	screenfaded = false;
+#endif
+}
+
+
+void VW_FadeOut(void)
+{
+#if GRMODE == EGAGR
+	int i;
+
+	for (i=3;i>=0;i--)
+	{
+	  colors[i][16] = bordercolor;
+	  _ES=FP_SEG(&colors[i]);
+	  _DX=FP_OFF(&colors[i]);
+	  _AX=0x1002;
+	  geninterrupt(0x10);
+	  VW_WaitVBL(6);
+	}
+	screenfaded = true;
+#endif
+}
+
+
+void VW_FadeIn(void)
+{
+#if GRMODE == EGAGR
+	int i;
+
+	for (i=0;i<4;i++)
+	{
+	  colors[i][16] = bordercolor;
+	  _ES=FP_SEG(&colors[i]);
+	  _DX=FP_OFF(&colors[i]);
+	  _AX=0x1002;
+	  geninterrupt(0x10);
+	  VW_WaitVBL(6);
+	}
+	screenfaded = false;
+#endif
+}
+
+void VW_FadeUp(void)
+{
+#if GRMODE == EGAGR
+	int i;
+
+	for (i=3;i<6;i++)
+	{
+	  colors[i][16] = bordercolor;
+	  _ES=FP_SEG(&colors[i]);
+	  _DX=FP_OFF(&colors[i]);
+	  _AX=0x1002;
+	  geninterrupt(0x10);
+	  VW_WaitVBL(6);
+	}
+	screenfaded = true;
+#endif
+}
+
+void VW_FadeDown(void)
+{
+#if GRMODE == EGAGR
+	int i;
+
+	for (i=5;i>2;i--)
+	{
+	  colors[i][16] = bordercolor;
+	  _ES=FP_SEG(&colors[i]);
+	  _DX=FP_OFF(&colors[i]);
+	  _AX=0x1002;
+	  geninterrupt(0x10);
+	  VW_WaitVBL(6);
+	}
+	screenfaded = false;
+#endif
+}
+
+
+/*
+========================
+=
+= VW_SetAtrReg
+=
+= Sets an attribute (pallete / border) register
+= Does NOT vsync!
+=
+========================
+*/
+
+void VW_SetAtrReg (int reg, int value)
+{
+  asm	cli
+  asm	mov	dx,STATUS_REGISTER_1
+  asm	in	al,dx
+  asm	mov	dx,ATR_INDEX
+
+  asm	mov	al,BYTE PTR [reg]
+  asm	out	dx,al
+  asm	mov	al,BYTE PTR [value]
+  asm	out	dx,al
+  asm	mov	dx,0x3da
+  asm	in	al,dx
+  asm	mov	dx,ATR_INDEX
+  asm	mov	al,0x20
+  asm	out	dx,al
+  asm	sti
+}
+
+
+
+//===========================================================================
+
+/*
+====================
+=
+= VW_SetLineWidth
+=
+= Must be an even number of bytes
+=
+====================
+*/
+
+void VW_SetLineWidth (int width)
+{
+  int i,offset;
+
+#if GRMODE == EGAGR
+//
+// set wide virtual screen
+//
+asm	mov	dx,CRTC_INDEX
+asm	mov	al,CRTC_OFFSET
+asm mov	ah,[BYTE PTR width]
+asm	shr	ah,1
+asm	out	dx,ax
+#endif
+
+//
+// set up lookup tables
+//
+  linewidth = width;
+
+  offset = 0;
+
+  for (i=0;i<VIRTUALHEIGHT;i++)
+  {
+	ylookup[i]=offset;
+	offset += width;
+  }
+}
+
+
+//===========================================================================
+
+/*
+====================
+=
+= VW_SetSplitScreen
+=
+====================
+*/
+#ifdef CAT3D
+void VW_SetSplitScreen (int linenum)
+{
+	VW_WaitVBL (1);
+	if (videocard==VGAcard)
+		linenum=linenum*2-1;
+	outportb (CRTC_INDEX,CRTC_LINECOMPARE);
+	outportb (CRTC_INDEX+1,linenum % 256);
+	outportb (CRTC_INDEX,CRTC_OVERFLOW);
+	outportb (CRTC_INDEX+1, 1+16*(linenum/256));
+	if (videocard==VGAcard)
+	{
+		outportb (CRTC_INDEX,CRTC_MAXSCANLINE);
+		outportb (CRTC_INDEX+1,inportb(CRTC_INDEX+1) & (255-64));
+	}
+}
+#endif
+//===========================================================================
+
+/*
+====================
+=
+= VW_ClearVideo
+=
+====================
+*/
+
+void	VW_ClearVideo (int color)
+{
+#if GRMODE == EGAGR
+	EGAWRITEMODE(2);
+	EGAMAPMASK(15);
+
+	color = (color << 8) & color;	//BUG: color is always 0 after this
+#endif
+
+#if GRMODE == CGAGR
+	color = (color << 12) & (color << 8) & (color << 4) & color;	//BUG: color is always 0 after this
+#endif
+
+	VW_WaitVBL(1);
+
+asm	mov	es, screenseg;
+asm	mov	di, displayofs;
+asm	and	di, not 1;
+asm	mov	cx, 8000h;
+asm	mov	ax, color;
+asm	rep stosw;
+
+#if GRMODE == EGAGR
+	EGAWRITEMODE(0);
+#endif
+}
+
+//===========================================================================
+
+#if NUMPICS>0
+
+/*
+====================
+=
+= VW_DrawPic
+=
+= X in bytes, y in pixels, chunknum is the #defined picnum
+=
+====================
+*/
+
+void VW_DrawPic(unsigned x, unsigned y, unsigned chunknum)
+{
+	int	picnum = chunknum - STARTPICS;
+	memptr source;
+	unsigned dest,width,height;
+
+	source = grsegs[chunknum];
+	dest = ylookup[y]+x+bufferofs;
+	width = pictable[picnum].width;
+	height = pictable[picnum].height;
+
+	VW_MemToScreen(source,dest,width,height);
+}
+
+
+#endif
+
+#if NUMPICM>0
+
+/*
+====================
+=
+= VW_DrawMPic
+=
+= X in bytes, y in pixels, chunknum is the #defined picnum
+=
+====================
+*/
+
+void VW_DrawMPic(unsigned x, unsigned y, unsigned chunknum)
+{
+	int	picnum = chunknum - STARTPICM;
+	memptr source;
+	unsigned dest,width,height;
+
+	source = grsegs[chunknum];
+	dest = ylookup[y]+x+bufferofs;
+	width = picmtable[picnum].width;
+	height = picmtable[picnum].height;
+
+	VW_MaskBlock(source,0,dest,width,height,width*height);
+}
+
+void VW_ClipDrawMPic(unsigned x, int y, unsigned chunknum)
+{
+	int	picnum = chunknum - STARTPICM;
+	memptr source;
+	unsigned dest,width,ofs,plane;
+	int		height;
+
+	source = grsegs[chunknum];
+	width = picmtable[picnum].width;
+	height = picmtable[picnum].height;
+	plane = width*height;
+
+	ofs = 0;
+	if (y<0)
+	{
+		ofs= -y*width;
+		height+=y;
+		y=0;
+	}
+	else if (y+height>216)
+	{
+		height-=(y-216);
+	}
+	dest = ylookup[y]+x+bufferofs;
+	if (height<1)
+		return;
+
+	VW_MaskBlock(source,ofs,dest,width,height,plane);
+}
+
+
+#endif
+
+//===========================================================================
+
+#if NUMSPRITES>0
+
+/*
+====================
+=
+= VW_DrawSprite
+=
+= X and Y in pixels, it will match the closest shift possible
+=
+= To do:
+= Add vertical clipping!
+= Make the shifts act as center points, rather than break points
+=
+====================
+*/
+
+void VW_DrawSprite(int x, int y, unsigned chunknum)
+{
+	spritetabletype far *spr;
+	spritetype _seg	*block;
+	unsigned	dest,shift;
+
+	spr = &spritetable[chunknum-STARTSPRITES];
+	block = (spritetype _seg *)grsegs[chunknum];
+
+	y+=spr->orgy>>G_P_SHIFT;
+	x+=spr->orgx>>G_P_SHIFT;
+
+#if GRMODE == EGAGR
+	shift = (x&7)/2;
+#endif
+#if GRMODE == CGAGR
+	shift = 0;
+#endif
+
+	dest = bufferofs + ylookup[y];
+	if (x>=0)
+		dest += x/SCREENXDIV;
+	else
+		dest += (x+1)/SCREENXDIV;
+
+	VW_MaskBlock (block,block->sourceoffset[shift],dest,
+		block->width[shift],spr->height,block->planesize[shift]);
+}
+
+#endif
+
+
+/*
+==================
+=
+= VW_Hlin
+=
+==================
+*/
+
+
+#if GRMODE == EGAGR
+
+unsigned char leftmask[8] = {0xff,0x7f,0x3f,0x1f,0xf,7,3,1};
+unsigned char rightmask[8] = {0x80,0xc0,0xe0,0xf0,0xf8,0xfc,0xfe,0xff};
+
+void VW_Hlin(unsigned xl, unsigned xh, unsigned y, unsigned color)
+{
+  unsigned dest,xlb,xhb,maskleft,maskright,mid;
+
+	xlb=xl/8;
+	xhb=xh/8;
+
+	EGAWRITEMODE(2);
+	EGAMAPMASK(15);
+
+	maskleft = leftmask[xl&7];
+	maskright = rightmask[xh&7];
+
+	mid = xhb-xlb-1;
+	dest = bufferofs+ylookup[y]+xlb;
+
+  if (xlb==xhb)
+  {
+  //
+  // entire line is in one byte
+  //
+
+	maskleft&=maskright;
+
+	asm	mov	es,[screenseg]
+	asm	mov	di,[dest]
+
+	asm	mov	dx,GC_INDEX
+	asm	mov	al,GC_BITMASK
+	asm	mov	ah,[BYTE PTR maskleft]
+	asm	out	dx,ax		// mask off pixels
+
+	asm	mov	al,[BYTE PTR color]
+	asm	xchg	al,[es:di]	// load latches and write pixels
+
+	goto	done;
+  }
+
+asm	mov	es,[screenseg]
+asm	mov	di,[dest]
+asm	mov	dx,GC_INDEX
+asm	mov	bh,[BYTE PTR color]
+
+//
+// draw left side
+//
+asm	mov	al,GC_BITMASK
+asm	mov	ah,[BYTE PTR maskleft]
+asm	out	dx,ax		// mask off pixels
+
+asm	mov	al,bh
+asm	mov	bl,[es:di]	// load latches
+asm	stosb
+
+//
+// draw middle
+//
+asm	mov	ax,GC_BITMASK + 255*256
+asm	out	dx,ax		// no masking
+
+asm	mov	al,bh
+asm	mov	cx,[mid]
+asm	rep	stosb
+
+//
+// draw right side
+//
+asm	mov	al,GC_BITMASK
+asm	mov	ah,[BYTE PTR maskright]
+asm	out	dx,ax		// mask off pixels
+
+asm	xchg	bh,[es:di]	// load latches and write pixels
+
+done:
+	EGABITMASK(255);
+	EGAWRITEMODE(0);
+}
+#endif
+
+
+#if GRMODE == CGAGR
+
+unsigned char pixmask[4] = {0xc0,0x30,0x0c,0x03};
+unsigned char leftmask[4] = {0xff,0x3f,0x0f,0x03};
+unsigned char rightmask[4] = {0xc0,0xf0,0xfc,0xff};
+unsigned char colorbyte[4] = {0,0x55,0xaa,0xff};
+
+//
+// could be optimized for rep stosw
+//
+void VW_Hlin(unsigned xl, unsigned xh, unsigned y, unsigned color)
+{
+	unsigned dest,xlb,xhb,mid;
+	byte maskleft,maskright;
+
+	color = colorbyte[color];	// expand 2 color bits to 8
+
+	xlb=xl/4;
+	xhb=xh/4;
+
+	maskleft = leftmask[xl&3];
+	maskright = rightmask[xh&3];
+
+	mid = xhb-xlb-1;
+	dest = bufferofs+ylookup[y]+xlb;
+asm	mov	es,[screenseg]
+
+	if (xlb==xhb)
+	{
+	//
+	// entire line is in one byte
+	//
+		maskleft&=maskright;
+
+		asm	mov	ah,[maskleft]
+		asm	mov	bl,[BYTE PTR color]
+		asm	and	bl,[maskleft]
+		asm	not	ah
+
+		asm	mov	di,[dest]
+
+		asm	mov	al,[es:di]
+		asm	and	al,ah			// mask out pixels
+		asm	or	al,bl			// or in color
+		asm	mov	[es:di],al
+		return;
+	}
+
+asm	mov	di,[dest]
+asm	mov	bh,[BYTE PTR color]
+
+//
+// draw left side
+//
+asm	mov	ah,[maskleft]
+asm	mov	bl,bh
+asm	and	bl,[maskleft]
+asm	not	ah
+asm	mov	al,[es:di]
+asm	and	al,ah			// mask out pixels
+asm	or	al,bl			// or in color
+asm	stosb
+
+//
+// draw middle
+//
+asm	mov	al,bh
+asm	mov	cx,[mid]
+asm	rep	stosb
+
+//
+// draw right side
+//
+asm	mov	ah,[maskright]
+asm	mov	bl,bh
+asm	and	bl,[maskright]
+asm	not	ah
+asm	mov	al,[es:di]
+asm	and	al,ah			// mask out pixels
+asm	or	al,bl			// or in color
+asm	stosb
+}
+#endif
+
+
+/*
+==================
+=
+= VW_Bar
+=
+= Pixel addressable block fill routine
+=
+==================
+*/
+
+#if GRMODE == CGAGR
+
+void VW_Bar (unsigned x, unsigned y, unsigned width, unsigned height,
+	unsigned color)
+{
+	unsigned xh = x+width-1;
+
+	while (height--)
+		VW_Hlin (x,xh,y++,color);
+}
+
+#endif
+
+
+#if	GRMODE == EGAGR
+
+void VW_Bar (unsigned x, unsigned y, unsigned width, unsigned height,
+	unsigned color)
+{
+	unsigned dest,xh,xlb,xhb,maskleft,maskright,mid;
+
+	xh = x+width-1;
+	xlb=x/8;
+	xhb=xh/8;
+
+	EGAWRITEMODE(2);
+	EGAMAPMASK(15);
+
+	maskleft = leftmask[x&7];
+	maskright = rightmask[xh&7];
+
+	mid = xhb-xlb-1;
+	dest = bufferofs+ylookup[y]+xlb;
+
+	if (xlb==xhb)
+	{
+	//
+	// entire line is in one byte
+	//
+
+		maskleft&=maskright;
+
+	asm	mov	es,[screenseg]
+	asm	mov	di,[dest]
+
+	asm	mov	dx,GC_INDEX
+	asm	mov	al,GC_BITMASK
+	asm	mov	ah,[BYTE PTR maskleft]
+	asm	out	dx,ax		// mask off pixels
+
+	asm	mov	ah,[BYTE PTR color]
+	asm	mov	dx,[linewidth]
+yloop1:
+	asm	mov	al,ah
+	asm	xchg	al,[es:di]	// load latches and write pixels
+	asm	add	di,dx			// down to next line
+	asm	dec	[height]
+	asm	jnz	yloop1
+
+		goto	done;
+	}
+
+asm	mov	es,[screenseg]
+asm	mov	di,[dest]
+asm	mov	bh,[BYTE PTR color]
+asm	mov	dx,GC_INDEX
+asm	mov	si,[linewidth]
+asm	sub	si,[mid]			// add to di at end of line to get to next scan
+asm	dec	si
+
+//
+// draw left side
+//
+yloop2:
+asm	mov	al,GC_BITMASK
+asm	mov	ah,[BYTE PTR maskleft]
+asm	out	dx,ax		// mask off pixels
+
+asm	mov	al,bh
+asm	mov	bl,[es:di]	// load latches
+asm	stosb
+
+//
+// draw middle
+//
+asm	mov	ax,GC_BITMASK + 255*256
+asm	out	dx,ax		// no masking
+
+asm	mov	al,bh
+asm	mov	cx,[mid]
+asm	rep	stosb
+
+//
+// draw right side
+//
+asm	mov	al,GC_BITMASK
+asm	mov	ah,[BYTE PTR maskright]
+asm	out	dx,ax		// mask off pixels
+
+asm	mov	al,bh
+asm	xchg	al,[es:di]	// load latches and write pixels
+
+asm	add	di,si		// move to start of next line
+asm	dec	[height]
+asm	jnz	yloop2
+
+done:
+	EGABITMASK(255);
+	EGAWRITEMODE(0);
+}
+
+#endif
+
+//==========================================================================
+
+/*
+==================
+=
+= VW_MeasureString
+=
+==================
+*/
+
+#if NUMFONT+NUMFONTM>0
+void
+VWL_MeasureString (char far *string, word *width, word *height, fontstruct _seg *font)
+{
+	*height = font->height;
+	for (*width = 0;*string;string++)
+		*width += font->width[*((byte far *)string)];	// proportional width
+}
+
+void	VW_MeasurePropString (char far *string, word *width, word *height)
+{
+	VWL_MeasureString(string,width,height,(fontstruct _seg *)grsegs[STARTFONT+fontnumber]);
+}
+
+void	VW_MeasureMPropString  (char far *string, word *width, word *height)
+{
+	VWL_MeasureString(string,width,height,(fontstruct _seg *)grsegs[STARTFONTM+fontnumber]);
+}
+
+
+#endif
+
+
+/*
+=============================================================================
+
+							CGA stuff
+
+=============================================================================
+*/
+
+#if GRMODE == CGAGR
+
+#define CGACRTCWIDTH	40
+
+/*
+==========================
+=
+= VW_CGAFullUpdate
+=
+==========================
+*/
+
+void VW_CGAFullUpdate (void)
+{
+	byte	*update;
+	boolean	halftile;
+	unsigned	x,y,middlerows,middlecollumns;
+
+	displayofs = bufferofs+panadjust;
+
+asm	mov	ax,0xb800
+asm	mov	es,ax
+
+asm	mov	si,[displayofs]
+asm	xor	di,di
+
+asm	mov	bx,100				// pairs of scan lines to copy
+asm	mov	dx,[linewidth]
+asm	sub	dx,80
+
+asm	mov	ds,[screenseg]
+asm	test	si,1
+asm	jz	evenblock
+
+//
+// odd source
+//
+asm	mov	ax,39				// words accross screen
+copytwolineso:
+asm	movsb
+asm	mov	cx,ax
+asm	rep	movsw
+asm	movsb
+asm	add	si,dx
+asm	add	di,0x2000-80		// go to the interlaced bank
+asm	movsb
+asm	mov	cx,ax
+asm	rep	movsw
+asm	movsb
+asm	add	si,dx
+asm	sub	di,0x2000			// go to the non interlaced bank
+
+asm	dec	bx
+asm	jnz	copytwolineso
+asm	jmp	blitdone
+
+//
+// even source
+//
+evenblock:
+asm	mov	ax,40				// words accross screen
+copytwolines:
+asm	mov	cx,ax
+asm	rep	movsw
+asm	add	si,dx
+asm	add	di,0x2000-80		// go to the interlaced bank
+asm	mov	cx,ax
+asm	rep	movsw
+asm	add	si,dx
+asm	sub	di,0x2000			// go to the non interlaced bank
+
+asm	dec	bx
+asm	jnz	copytwolines
+
+blitdone:
+asm	mov	ax,ss
+asm	mov	ds,ax
+asm	mov	es,ax
+
+asm	xor	ax,ax				// clear out the update matrix
+asm	mov	cx,UPDATEWIDE*UPDATEHIGH/2
+
+asm	mov	di,[baseupdateptr]
+asm	rep	stosw
+
+	updateptr = baseupdateptr;
+	*(unsigned *)(updateptr + UPDATEWIDE*PORTTILESHIGH) = UPDATETERMINATE;
+}
+
+
+#endif
+
+/*
+=============================================================================
+
+					   CURSOR ROUTINES
+
+These only work in the context of the double buffered update routines
+
+=============================================================================
+*/
+
+/*
+====================
+=
+= VWL_DrawCursor
+=
+= Background saves, then draws the cursor at cursorspot
+=
+====================
+*/
+
+void VWL_DrawCursor (void)
+{
+	cursorspot = bufferofs + ylookup[cursory+pansy]+(cursorx+pansx)/SCREENXDIV;
+	VW_ScreenToMem(cursorspot,cursorsave,cursorwidth,cursorheight);
+	VWB_DrawSprite(cursorx,cursory,cursornumber);
+}
+
+
+//==========================================================================
+
+
+/*
+====================
+=
+= VWL_EraseCursor
+=
+====================
+*/
+
+void VWL_EraseCursor (void)
+{
+	VW_MemToScreen(cursorsave,cursorspot,cursorwidth,cursorheight);
+	VW_MarkUpdateBlock ((cursorx+pansx)&SCREENXMASK,cursory+pansy,
+		( (cursorx+pansx)&SCREENXMASK)+cursorwidth*SCREENXDIV-1,
+		cursory+pansy+cursorheight-1);
+}
+
+
+//==========================================================================
+
+
+/*
+====================
+=
+= VW_ShowCursor
+=
+====================
+*/
+
+void VW_ShowCursor (void)
+{
+	cursorvisible++;
+}
+
+
+//==========================================================================
+
+/*
+====================
+=
+= VW_HideCursor
+=
+====================
+*/
+
+void VW_HideCursor (void)
+{
+	cursorvisible--;
+}
+
+//==========================================================================
+
+/*
+====================
+=
+= VW_MoveCursor
+=
+====================
+*/
+#define MAXCURSORX	(319-24)
+#define MAXCURSORY	(199-24)
+
+void VW_MoveCursor (int x, int y)
+{
+#ifdef CAT3D
+	if (x>MAXCURSORX)
+		x=MAXCURSORX;
+	if (y>MAXCURSORY)
+		y=MAXCURSORY;			// catacombs hack to keep cursor on screen
+#endif
+
+	cursorx = x;
+	cursory = y;
+}
+
+//==========================================================================
+
+/*
+====================
+=
+= VW_SetCursor
+=
+= Load in a sprite to be used as a cursor, and allocate background save space
+=
+====================
+*/
+
+void VW_SetCursor (int spritenum)
+{
+	VW_FreeCursor ();
+
+	cursornumber = spritenum;
+
+	CA_CacheGrChunk (spritenum);
+	MM_SetLock (&grsegs[spritenum],true);
+
+	cursorwidth = spritetable[spritenum-STARTSPRITES].width+1;
+	cursorheight = spritetable[spritenum-STARTSPRITES].height;
+
+	MM_GetPtr (&cursorsave,cursorwidth*cursorheight*5);
+	MM_SetLock (&cursorsave,true);
+}
+
+
+/*
+====================
+=
+= VW_FreeCursor
+=
+= Frees the memory used by the cursor and its background save
+=
+====================
+*/
+
+void VW_FreeCursor (void)
+{
+	if (cursornumber)
+	{
+		MM_SetLock (&grsegs[cursornumber],false);
+		MM_SetPurge (&grsegs[cursornumber],3);
+		MM_SetLock (&cursorsave,false);
+		MM_FreePtr (&cursorsave);
+		cursornumber = 0;
+	}
+}
+
+
+/*
+=============================================================================
+
+				Double buffer management routines
+
+=============================================================================
+*/
+
+/*
+======================
+=
+= VW_InitDoubleBuffer
+=
+======================
+*/
+
+void VW_InitDoubleBuffer (void)
+{
+#if GRMODE == EGAGR
+	VW_SetScreen (displayofs+panadjust,0);			// no pel pan
+#endif
+}
+
+
+/*
+======================
+=
+= VW_FixRefreshBuffer
+=
+= Copies the view page to the buffer page on page flipped refreshes to
+= avoid a one frame shear around pop up windows
+=
+======================
+*/
+
+void VW_FixRefreshBuffer (void)
+{
+#if GRMODE == EGAGR
+	VW_ScreenToScreen (displayofs,bufferofs,PORTTILESWIDE*4*CHARWIDTH,
+		(PORTTILESHIGH-1)*16);
+#endif
+}
+
+
+/*
+======================
+=
+= VW_QuitDoubleBuffer
+=
+======================
+*/
+
+void VW_QuitDoubleBuffer (void)
+{
+}
+
+
+/*
+=======================
+=
+= VW_MarkUpdateBlock
+=
+= Takes a pixel bounded block and marks the tiles in bufferblocks
+= Returns 0 if the entire block is off the buffer screen
+=
+=======================
+*/
+
+int VW_MarkUpdateBlock (int x1, int y1, int x2, int y2)
+{
+	int	x,y,xt1,yt1,xt2,yt2,nextline;
+	byte *mark;
+
+	xt1 = x1>>PIXTOBLOCK;
+	yt1 = y1>>PIXTOBLOCK;
+
+	xt2 = x2>>PIXTOBLOCK;
+	yt2 = y2>>PIXTOBLOCK;
+
+	if (xt1<0)
+		xt1=0;
+	else if (xt1>=UPDATEWIDE-1)
+		return 0;
+
+	if (yt1<0)
+		yt1=0;
+	else if (yt1>UPDATEHIGH)
+		return 0;
+
+	if (xt2<0)
+		return 0;
+	else if (xt2>=UPDATEWIDE-1)
+		xt2 = UPDATEWIDE-2;
+
+	if (yt2<0)
+		return 0;
+	else if (yt2>=UPDATEHIGH)
+		yt2 = UPDATEHIGH-1;
+
+	mark = updateptr + uwidthtable[yt1] + xt1;
+	nextline = UPDATEWIDE - (xt2-xt1) - 1;
+
+	for (y=yt1;y<=yt2;y++)
+	{
+		for (x=xt1;x<=xt2;x++)
+			*mark++ = 1;			// this tile will need to be updated
+
+		mark += nextline;
+	}
+
+	return 1;
+}
+
+
+/*
+===========================
+=
+= VW_UpdateScreen
+=
+= Updates any changed areas of the double buffer and displays the cursor
+=
+===========================
+*/
+
+void VW_UpdateScreen (void)
+{
+	if (cursorvisible>0)
+		VWL_DrawCursor();
+
+#if GRMODE == EGAGR
+	VWL_UpdateScreenBlocks();
+#endif
+#if GRMODE == CGAGR
+	VW_CGAFullUpdate();
+#endif
+
+	if (cursorvisible>0)
+		VWL_EraseCursor();
+}
+
+
+
+void VWB_DrawTile8 (int x, int y, int tile)
+{
+	x+=pansx;
+	y+=pansy;
+	if (VW_MarkUpdateBlock (x&SCREENXMASK,y,(x&SCREENXMASK)+7,y+7))
+		VW_DrawTile8 (x/SCREENXDIV,y,tile);
+}
+
+void VWB_DrawTile8M (int x, int y, int tile)
+{
+	int xb;
+
+	x+=pansx;
+	y+=pansy;
+	xb = x/SCREENXDIV; 			// use intermediate because VW_DT8M is macro
+	if (VW_MarkUpdateBlock (x&SCREENXMASK,y,(x&SCREENXMASK)+7,y+7))
+		VW_DrawTile8M (xb,y,tile);
+}
+
+void VWB_DrawTile16 (int x, int y, int tile)
+{
+	x+=pansx;
+	y+=pansy;
+	if (VW_MarkUpdateBlock (x&SCREENXMASK,y,(x&SCREENXMASK)+15,y+15))
+		VW_DrawTile16 (x/SCREENXDIV,y,tile);
+}
+
+void VWB_DrawTile16M (int x, int y, int tile)
+{
+	int xb;
+
+	x+=pansx;
+	y+=pansy;
+	xb = x/SCREENXDIV;		// use intermediate because VW_DT16M is macro
+	if (VW_MarkUpdateBlock (x&SCREENXMASK,y,(x&SCREENXMASK)+15,y+15))
+		VW_DrawTile16M (xb,y,tile);
+}
+
+#if NUMPICS
+void VWB_DrawPic (int x, int y, int chunknum)
+{
+// mostly copied from drawpic
+	int	picnum = chunknum - STARTPICS;
+	memptr source;
+	unsigned dest,width,height;
+
+	x+=pansx;
+	y+=pansy;
+	x/= SCREENXDIV;
+
+	source = grsegs[chunknum];
+	dest = ylookup[y]+x+bufferofs;
+	width = pictable[picnum].width;
+	height = pictable[picnum].height;
+
+	if (VW_MarkUpdateBlock (x*SCREENXDIV,y,(x+width)*SCREENXDIV-1,y+height-1))
+		VW_MemToScreen(source,dest,width,height);
+}
+#endif
+
+#if NUMPICM>0
+void VWB_DrawMPic(int x, int y, int chunknum)
+{
+// mostly copied from drawmpic
+	int	picnum = chunknum - STARTPICM;
+	memptr source;
+	unsigned dest,width,height;
+
+	x+=pansx;
+	y+=pansy;
+	x/=SCREENXDIV;
+
+	source = grsegs[chunknum];
+	dest = ylookup[y]+x+bufferofs;
+	width = picmtable[picnum].width;
+	height = picmtable[picnum].height;
+
+	if (VW_MarkUpdateBlock (x*SCREENXDIV,y,(x+width)*SCREENXDIV-1,y+height-1))
+		VW_MaskBlock(source,0,dest,width,height,width*height);
+}
+#endif
+
+
+void VWB_Bar (int x, int y, int width, int height, int color)
+{
+	x+=pansx;
+	y+=pansy;
+	if (VW_MarkUpdateBlock (x,y,x+width,y+height-1) )
+		VW_Bar (x,y,width,height,color);
+}
+
+
+#if NUMFONT
+void VWB_DrawPropString	 (char far *string)
+{
+	int x,y;
+	x = px+pansx;
+	y = py+pansy;
+	VW_DrawPropString (string);
+	VW_MarkUpdateBlock(x,y,x+bufferwidth*8-1,y+bufferheight-1);
+}
+#endif
+
+
+#if NUMFONTM
+void VWB_DrawMPropString (char far *string)
+{
+	int x,y;
+	x = px+pansx;
+	y = py+pansy;
+	VW_DrawMPropString (string);
+	VW_MarkUpdateBlock(x,y,x+bufferwidth*8-1,y+bufferheight-1);
+}
+#endif
+
+#if NUMSPRITES
+void VWB_DrawSprite(int x, int y, int chunknum)
+{
+	spritetabletype far *spr;
+	spritetype _seg	*block;
+	unsigned	dest,shift,width,height;
+
+	x+=pansx;
+	y+=pansy;
+
+	spr = &spritetable[chunknum-STARTSPRITES];
+	block = (spritetype _seg *)grsegs[chunknum];
+
+	y+=spr->orgy>>G_P_SHIFT;
+	x+=spr->orgx>>G_P_SHIFT;
+
+
+#if GRMODE == EGAGR
+	shift = (x&7)/2;
+#endif
+#if GRMODE == CGAGR
+	shift = 0;
+#endif
+
+	dest = bufferofs + ylookup[y];
+	if (x>=0)
+		dest += x/SCREENXDIV;
+	else
+		dest += (x+1)/SCREENXDIV;
+
+	width = block->width[shift];
+	height = spr->height;
+
+	if (VW_MarkUpdateBlock (x&SCREENXMASK,y,(x&SCREENXMASK)+width*SCREENXDIV-1
+		,y+height-1))
+		VW_MaskBlock (block,block->sourceoffset[shift],dest,
+			width,height,block->planesize[shift]);
+}
+#endif
+
+void VWB_Plot (int x, int y, int color)
+{
+	x+=pansx;
+	y+=pansy;
+	if (VW_MarkUpdateBlock (x,y,x,y))
+		VW_Plot(x,y,color);
+}
+
+void VWB_Hlin (int x1, int x2, int y, int color)
+{
+	x1+=pansx;
+	x2+=pansx;
+	y+=pansy;
+	if (VW_MarkUpdateBlock (x1,y,x2,y))
+		VW_Hlin(x1,x2,y,color);
+}
+
+void VWB_Vlin (int y1, int y2, int x, int color)
+{
+	x+=pansx;
+	y1+=pansy;
+	y2+=pansy;
+	if (VW_MarkUpdateBlock (x,y1,x,y2))
+		VW_Vlin(y1,y2,x,color);
+}
+
+
+//===========================================================================
diff --git a/16/keen456/KEEN4-6/ID_VW.H b/16/keen456/KEEN4-6/ID_VW.H
new file mode 100755
index 00000000..65e98679
--- /dev/null
+++ b/16/keen456/KEEN4-6/ID_VW.H
@@ -0,0 +1,381 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+// ID_VW.H
+
+#ifndef __TYPES__
+#include "ID_TYPES.H"
+#endif
+
+#ifndef __ID_MM__
+#include "ID_MM.H"
+#endif
+
+#ifndef __ID_GLOB__
+#include "ID_GLOB.H"
+#endif
+
+#define __ID_VW__
+
+//===========================================================================
+
+#define	G_P_SHIFT		4	// global >> ?? = pixels
+
+#if GRMODE == EGAGR
+#ifdef CAT3D
+#define	SCREENWIDTH		40
+#else
+#define	SCREENWIDTH		64
+#endif
+#define CHARWIDTH		1
+#define TILEWIDTH		2
+#define GRPLANES		4
+#define BYTEPIXELS		8
+#endif
+
+#if GRMODE == CGAGR
+#define	SCREENWIDTH		128
+#define CHARWIDTH		2
+#define TILEWIDTH		4
+#define GRPLANES		1
+#define BYTEPIXELS		4
+#endif
+
+#define VIRTUALHEIGHT	300
+#define	VIRTUALWIDTH	512
+
+
+#if GRMODE == CGAGR
+
+#define	MAXSHIFTS		1
+
+#define WHITE			3			// graphics mode independant colors
+#define BLACK			0
+#define FIRSTCOLOR		1
+#define SECONDCOLOR		2
+#define F_WHITE			0			// for XOR font drawing
+#define F_BLACK			3
+#define F_FIRSTCOLOR	2
+#define F_SECONDCOLOR	1
+
+#endif
+
+#if GRMODE == EGAGR
+
+#define	MAXSHIFTS		4
+
+#define WHITE			15			// graphics mode independant colors
+#define BLACK			0
+#define FIRSTCOLOR		1
+#define SECONDCOLOR		12
+#define F_WHITE			0			// for XOR font drawing
+#define F_BLACK			15
+#define F_FIRSTCOLOR	14
+#define F_SECONDCOLOR	3
+
+#endif
+
+#if GRMODE == EGAGR
+#define SCREENXMASK		(~7)
+#define SCREENXPLUS		(7)
+#define SCREENXDIV		(8)
+#endif
+
+#if GRMODE == CGAGR
+#define SCREENXMASK		(~3)
+#define SCREENXDIV		(4)
+#endif
+
+//===========================================================================
+
+
+#define SC_INDEX	0x3C4
+#define SC_RESET	0
+#define SC_CLOCK	1
+#define SC_MAPMASK	2
+#define SC_CHARMAP	3
+#define SC_MEMMODE	4
+
+#define CRTC_INDEX	0x3D4
+#define CRTC_H_TOTAL	0
+#define CRTC_H_DISPEND	1
+#define CRTC_H_BLANK	2
+#define CRTC_H_ENDBLANK	3
+#define CRTC_H_RETRACE	4
+#define CRTC_H_ENDRETRACE 5
+#define CRTC_V_TOTAL	6
+#define CRTC_OVERFLOW	7
+#define CRTC_ROWSCAN	8
+#define CRTC_MAXSCANLINE 9
+#define CRTC_CURSORSTART 10
+#define CRTC_CURSOREND	11
+#define CRTC_STARTHIGH	12
+#define CRTC_STARTLOW	13
+#define CRTC_CURSORHIGH	14
+#define CRTC_CURSORLOW	15
+#define CRTC_V_RETRACE	16
+#define CRTC_V_ENDRETRACE 17
+#define CRTC_V_DISPEND	18
+#define CRTC_OFFSET	19
+#define CRTC_UNDERLINE	20
+#define CRTC_V_BLANK	21
+#define CRTC_V_ENDBLANK	22
+#define CRTC_MODE	23
+#define CRTC_LINECOMPARE 24
+
+
+#define GC_INDEX	0x3CE
+#define GC_SETRESET	0
+#define GC_ENABLESETRESET 1
+#define GC_COLORCOMPARE	2
+#define GC_DATAROTATE	3
+#define GC_READMAP	4
+#define GC_MODE		5
+#define GC_MISCELLANEOUS 6
+#define GC_COLORDONTCARE 7
+#define GC_BITMASK	8
+
+#define ATR_INDEX	0x3c0
+#define ATR_MODE	16
+#define ATR_OVERSCAN	17
+#define ATR_COLORPLANEENABLE 18
+#define ATR_PELPAN	19
+#define ATR_COLORSELECT	20
+
+#define	STATUS_REGISTER_1    0x3da
+
+//===========================================================================
+
+typedef enum {NOcard,MDAcard,CGAcard,EGAcard,MCGAcard,VGAcard,
+		  HGCcard=0x80,HGCPcard,HICcard} cardtype;
+
+typedef struct
+{
+  int	width,
+	height,
+	orgx,orgy,
+	xl,yl,xh,yh,
+	shifts;
+} spritetabletype;
+
+typedef	struct
+{
+	unsigned	sourceoffset[MAXSHIFTS];
+	unsigned	planesize[MAXSHIFTS];
+	unsigned	width[MAXSHIFTS];
+	byte		data[];
+} spritetype;		// the memptr for each sprite points to this
+
+typedef struct
+{
+	int width,height;
+} pictabletype;
+
+
+typedef struct
+{
+	int height;
+	int location[256];
+	char width[256];
+} fontstruct;
+
+
+typedef enum {CGAgr,EGAgr,VGAgr} grtype;
+
+//===========================================================================
+
+extern	cardtype	videocard;		// set by VW_Startup
+extern	grtype		grmode;			// CGAgr, EGAgr, VGAgr
+
+extern	unsigned	bufferofs;		// hidden port to draw to before displaying
+extern	unsigned	displayofs;		// origin of port on visable screen
+extern	unsigned	panx,pany;		// panning adjustments inside port in pixels
+extern	unsigned	pansx,pansy;
+extern	unsigned	panadjust;		// panx/pany adjusted by screen resolution
+
+extern	unsigned	screenseg;		// normally 0xa000 or buffer segment
+
+extern	unsigned	linewidth;
+extern	unsigned	ylookup[VIRTUALHEIGHT];
+
+extern	boolean		screenfaded;
+extern	char 		colors[7][17];	// pallets for fades
+
+extern	pictabletype	_seg *pictable;
+extern	pictabletype	_seg *picmtable;
+extern	spritetabletype _seg *spritetable;
+
+extern	unsigned	fontnumber;		// 0 based font number for drawing
+extern	int			px,py;
+extern	byte		pdrawmode,fontcolor;
+
+extern	int			bordercolor;
+extern	boolean			nopan;
+
+//
+// asm globals
+//
+
+extern	unsigned	*shifttabletable[8];
+extern	unsigned	bufferwidth,bufferheight,screenspot;	// used by font drawing stuff
+
+
+
+//===========================================================================
+
+
+void	VW_Startup (void);
+void	VW_Shutdown (void);
+
+cardtype	VW_VideoID (void);
+
+//
+// EGA hardware routines
+//
+
+#define EGAWRITEMODE(x) asm{cli;mov dx,GC_INDEX;mov ax,GC_MODE+256*x;out dx,ax;sti;}
+#define EGABITMASK(x) asm{cli;mov dx,GC_INDEX;mov ax,GC_BITMASK+256*x;out dx,ax;sti;}
+#define EGAMAPMASK(x) asm{cli;mov dx,SC_INDEX;mov ax,SC_MAPMASK+x*256;out dx,ax;sti;}
+#define EGAREADMAP(x) asm{cli;mov dx,GC_INDEX;mov ax,GC_READMAP+x*256;out dx,ax;sti;}
+
+void 	VW_SetLineWidth(int width);
+void 	VW_SetSplitScreen(int width);
+void 	VW_SetScreen (unsigned CRTC, unsigned pelpan);
+
+void	VW_SetScreenMode (int grmode);
+void	VW_ClearVideo (int color);
+void	VW_WaitVBL (int number);
+
+void	VW_ColorBorder (int color);
+void 	VW_SetPalette(byte *palette);
+void	VW_SetDefaultColors(void);
+void	VW_FadeOut(void);
+void	VW_FadeIn(void);
+void	VW_FadeUp(void);
+void	VW_FadeDown(void);
+
+void	VW_SetAtrReg (int reg, int value);
+
+//
+// block primitives
+//
+
+void VW_MaskBlock(memptr segm,unsigned ofs,unsigned dest,
+	unsigned wide,unsigned height,unsigned planesize);
+void VW_InverseMask(memptr segm,unsigned ofs,unsigned dest,
+	unsigned wide,unsigned height);
+void VW_MemToScreen(memptr source,unsigned dest,unsigned width,unsigned height);
+void VW_ScreenToMem(unsigned source,memptr dest,unsigned width,unsigned height);
+void VW_ScreenToScreen(unsigned source,unsigned dest,unsigned width,unsigned height);
+
+
+//
+// block addressable routines
+//
+
+void VW_DrawTile8(unsigned x, unsigned y, unsigned tile);
+
+#if GRMODE == EGAGR
+
+#define VW_DrawTile8M(x,y,t) \
+	VW_MaskBlock(grsegs[STARTTILE8M],(t)*40,bufferofs+ylookup[y]+(x),1,8,8)
+#define VW_DrawTile16(x,y,t) \
+	VW_MemToScreen(grsegs[STARTTILE16+t],bufferofs+ylookup[y]+(x),2,16)
+#define VW_DrawTile16M(x,y,t) \
+	VW_MaskBlock(grsegs[STARTTILE16M],(t)*160,bufferofs+ylookup[y]+(x),2,16,32)
+
+#endif
+
+#if GRMODE == CGAGR
+
+#define VW_DrawTile8M(x,y,t) \
+	VW_MaskBlock(grsegs[STARTTILE8M],(t)*32,bufferofs+ylookup[y]+(x),2,8,16)
+#define VW_DrawTile16(x,y,t) \
+	VW_MemToScreen(grsegs[STARTTILE16+t],bufferofs+ylookup[y]+(x),4,16)
+#define VW_DrawTile16M(x,y,t) \
+	VW_MaskBlock(grsegs[STARTTILE16M],(t)*128,bufferofs+ylookup[y]+(x),4,16,64)
+
+#endif
+
+void VW_DrawPic(unsigned x, unsigned y, unsigned chunknum);
+void VW_DrawMPic(unsigned x, unsigned y, unsigned chunknum);
+void VW_ClipDrawMPic(unsigned x, int y, unsigned chunknum);
+
+//
+// pixel addressable routines
+//
+void	VW_MeasurePropString (char far *string, word *width, word *height);
+void	VW_MeasureMPropString  (char far *string, word *width, word *height);
+
+void VW_DrawPropString (char far *string);
+void VW_DrawMPropString (char far *string);
+void VW_DrawSprite(int x, int y, unsigned sprite);
+void VW_Plot(unsigned x, unsigned y, unsigned color);
+void VW_Hlin(unsigned xl, unsigned xh, unsigned y, unsigned color);
+void VW_Vlin(unsigned yl, unsigned yh, unsigned x, unsigned color);
+void VW_Bar (unsigned x, unsigned y, unsigned width, unsigned height,
+	unsigned color);
+
+//===========================================================================
+
+//
+// Double buffer management routines
+//
+
+void VW_InitDoubleBuffer (void);
+void VW_FixRefreshBuffer (void);
+int	 VW_MarkUpdateBlock (int x1, int y1, int x2, int y2);
+void VW_UpdateScreen (void);
+void VW_CGAFullUpdate (void);
+
+//
+// cursor
+//
+
+void VW_ShowCursor (void);
+void VW_HideCursor (void);
+void VW_MoveCursor (int x, int y);
+void VW_SetCursor (int spritenum);
+void VW_FreeCursor (void);
+
+//
+// mode independant routines
+// coordinates in pixels, rounded to best screen res
+// regions marked in double buffer
+//
+
+void VWB_DrawTile8 (int x, int y, int tile);
+void VWB_DrawTile8M (int x, int y, int tile);
+void VWB_DrawTile16 (int x, int y, int tile);
+void VWB_DrawTile16M (int x, int y, int tile);
+void VWB_DrawPic (int x, int y, int chunknum);
+void VWB_DrawMPic(int x, int y, int chunknum);
+void VWB_Bar (int x, int y, int width, int height, int color);
+
+void VWB_DrawPropString	 (char far *string);
+void VWB_DrawMPropString (char far *string);
+void VWB_DrawSprite (int x, int y, int chunknum);
+void VWB_Plot (int x, int y, int color);
+void VWB_Hlin (int x1, int x2, int y, int color);
+void VWB_Vlin (int y1, int y2, int x, int color);
+
+//===========================================================================
diff --git a/16/keen456/KEEN4-6/ID_VW_A.ASM b/16/keen456/KEEN4-6/ID_VW_A.ASM
new file mode 100755
index 00000000..3c5132e3
--- /dev/null
+++ b/16/keen456/KEEN4-6/ID_VW_A.ASM
@@ -0,0 +1,732 @@
+; Catacomb 3-D Source Code
+; Copyright (C) 1993-2014 Flat Rock Software
+;
+; This program is free software; you can redistribute it and/or modify
+; it under the terms of the GNU General Public License as published by
+; the Free Software Foundation; either version 2 of the License, or
+; (at your option) any later version.
+;
+; This program is distributed in the hope that it will be useful,
+; but WITHOUT ANY WARRANTY; without even the implied warranty of
+; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+; GNU General Public License for more details.
+;
+; You should have received a copy of the GNU General Public License along
+; with this program; if not, write to the Free Software Foundation, Inc.,
+; 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+
+; ID_VW_A.ASM
+
+IDEAL
+MODEL	MEDIUM,C
+
+INCLUDE	"ID_ASM.EQU"
+
+WAITFORVBL	=	1			; setting to 0 causes setscreen and waitvbl
+							; to skip waiting for VBL (for timing things)
+
+;============================================================================
+
+DATASEG
+
+EXTRN	screenseg			:WORD
+EXTRN	drawofs				:WORD
+EXTRN	bufferofs			:WORD
+EXTRN	displayofs			:WORD
+EXTRN	drawofs				:WORD
+EXTRN	panadjust			:WORD
+EXTRN	ylookup				:WORD
+EXTRN	linewidth			:WORD
+EXTRN	grsegs				:WORD
+EXTRN	updateptr			:WORD
+EXTRN	blockstarts			:WORD	;offsets from drawofs for each update block
+EXTRN	fontspace			:WORD
+EXTRN	fontnumber			:WORD
+
+
+planemask	db	?
+planenum	db	?
+screendest	dw	?
+linedelta	dw	?
+
+LABEL shiftdata0 WORD
+	dw     0,    1,    2,    3,    4,    5,    6,    7,    8,    9,   10,   11,   12,   13
+	dw    14,   15,   16,   17,   18,   19,   20,   21,   22,   23,   24,   25,   26,   27
+	dw    28,   29,   30,   31,   32,   33,   34,   35,   36,   37,   38,   39,   40,   41
+	dw    42,   43,   44,   45,   46,   47,   48,   49,   50,   51,   52,   53,   54,   55
+	dw    56,   57,   58,   59,   60,   61,   62,   63,   64,   65,   66,   67,   68,   69
+	dw    70,   71,   72,   73,   74,   75,   76,   77,   78,   79,   80,   81,   82,   83
+	dw    84,   85,   86,   87,   88,   89,   90,   91,   92,   93,   94,   95,   96,   97
+	dw    98,   99,  100,  101,  102,  103,  104,  105,  106,  107,  108,  109,  110,  111
+	dw   112,  113,  114,  115,  116,  117,  118,  119,  120,  121,  122,  123,  124,  125
+	dw   126,  127,  128,  129,  130,  131,  132,  133,  134,  135,  136,  137,  138,  139
+	dw   140,  141,  142,  143,  144,  145,  146,  147,  148,  149,  150,  151,  152,  153
+	dw   154,  155,  156,  157,  158,  159,  160,  161,  162,  163,  164,  165,  166,  167
+	dw   168,  169,  170,  171,  172,  173,  174,  175,  176,  177,  178,  179,  180,  181
+	dw   182,  183,  184,  185,  186,  187,  188,  189,  190,  191,  192,  193,  194,  195
+	dw   196,  197,  198,  199,  200,  201,  202,  203,  204,  205,  206,  207,  208,  209
+	dw   210,  211,  212,  213,  214,  215,  216,  217,  218,  219,  220,  221,  222,  223
+	dw   224,  225,  226,  227,  228,  229,  230,  231,  232,  233,  234,  235,  236,  237
+	dw   238,  239,  240,  241,  242,  243,  244,  245,  246,  247,  248,  249,  250,  251
+	dw   252,  253,  254,  255
+
+LABEL shiftdata1 WORD
+	dw     0,32768,    1,32769,    2,32770,    3,32771,    4,32772,    5,32773,    6,32774
+	dw     7,32775,    8,32776,    9,32777,   10,32778,   11,32779,   12,32780,   13,32781
+	dw    14,32782,   15,32783,   16,32784,   17,32785,   18,32786,   19,32787,   20,32788
+	dw    21,32789,   22,32790,   23,32791,   24,32792,   25,32793,   26,32794,   27,32795
+	dw    28,32796,   29,32797,   30,32798,   31,32799,   32,32800,   33,32801,   34,32802
+	dw    35,32803,   36,32804,   37,32805,   38,32806,   39,32807,   40,32808,   41,32809
+	dw    42,32810,   43,32811,   44,32812,   45,32813,   46,32814,   47,32815,   48,32816
+	dw    49,32817,   50,32818,   51,32819,   52,32820,   53,32821,   54,32822,   55,32823
+	dw    56,32824,   57,32825,   58,32826,   59,32827,   60,32828,   61,32829,   62,32830
+	dw    63,32831,   64,32832,   65,32833,   66,32834,   67,32835,   68,32836,   69,32837
+	dw    70,32838,   71,32839,   72,32840,   73,32841,   74,32842,   75,32843,   76,32844
+	dw    77,32845,   78,32846,   79,32847,   80,32848,   81,32849,   82,32850,   83,32851
+	dw    84,32852,   85,32853,   86,32854,   87,32855,   88,32856,   89,32857,   90,32858
+	dw    91,32859,   92,32860,   93,32861,   94,32862,   95,32863,   96,32864,   97,32865
+	dw    98,32866,   99,32867,  100,32868,  101,32869,  102,32870,  103,32871,  104,32872
+	dw   105,32873,  106,32874,  107,32875,  108,32876,  109,32877,  110,32878,  111,32879
+	dw   112,32880,  113,32881,  114,32882,  115,32883,  116,32884,  117,32885,  118,32886
+	dw   119,32887,  120,32888,  121,32889,  122,32890,  123,32891,  124,32892,  125,32893
+	dw   126,32894,  127,32895
+
+LABEL shiftdata2 WORD
+	dw     0,16384,32768,49152,    1,16385,32769,49153,    2,16386,32770,49154,    3,16387
+	dw 32771,49155,    4,16388,32772,49156,    5,16389,32773,49157,    6,16390,32774,49158
+	dw     7,16391,32775,49159,    8,16392,32776,49160,    9,16393,32777,49161,   10,16394
+	dw 32778,49162,   11,16395,32779,49163,   12,16396,32780,49164,   13,16397,32781,49165
+	dw    14,16398,32782,49166,   15,16399,32783,49167,   16,16400,32784,49168,   17,16401
+	dw 32785,49169,   18,16402,32786,49170,   19,16403,32787,49171,   20,16404,32788,49172
+	dw    21,16405,32789,49173,   22,16406,32790,49174,   23,16407,32791,49175,   24,16408
+	dw 32792,49176,   25,16409,32793,49177,   26,16410,32794,49178,   27,16411,32795,49179
+	dw    28,16412,32796,49180,   29,16413,32797,49181,   30,16414,32798,49182,   31,16415
+	dw 32799,49183,   32,16416,32800,49184,   33,16417,32801,49185,   34,16418,32802,49186
+	dw    35,16419,32803,49187,   36,16420,32804,49188,   37,16421,32805,49189,   38,16422
+	dw 32806,49190,   39,16423,32807,49191,   40,16424,32808,49192,   41,16425,32809,49193
+	dw    42,16426,32810,49194,   43,16427,32811,49195,   44,16428,32812,49196,   45,16429
+	dw 32813,49197,   46,16430,32814,49198,   47,16431,32815,49199,   48,16432,32816,49200
+	dw    49,16433,32817,49201,   50,16434,32818,49202,   51,16435,32819,49203,   52,16436
+	dw 32820,49204,   53,16437,32821,49205,   54,16438,32822,49206,   55,16439,32823,49207
+	dw    56,16440,32824,49208,   57,16441,32825,49209,   58,16442,32826,49210,   59,16443
+	dw 32827,49211,   60,16444,32828,49212,   61,16445,32829,49213,   62,16446,32830,49214
+	dw    63,16447,32831,49215
+
+LABEL shiftdata3 WORD
+	dw     0, 8192,16384,24576,32768,40960,49152,57344,    1, 8193,16385,24577,32769,40961
+	dw 49153,57345,    2, 8194,16386,24578,32770,40962,49154,57346,    3, 8195,16387,24579
+	dw 32771,40963,49155,57347,    4, 8196,16388,24580,32772,40964,49156,57348,    5, 8197
+	dw 16389,24581,32773,40965,49157,57349,    6, 8198,16390,24582,32774,40966,49158,57350
+	dw     7, 8199,16391,24583,32775,40967,49159,57351,    8, 8200,16392,24584,32776,40968
+	dw 49160,57352,    9, 8201,16393,24585,32777,40969,49161,57353,   10, 8202,16394,24586
+	dw 32778,40970,49162,57354,   11, 8203,16395,24587,32779,40971,49163,57355,   12, 8204
+	dw 16396,24588,32780,40972,49164,57356,   13, 8205,16397,24589,32781,40973,49165,57357
+	dw    14, 8206,16398,24590,32782,40974,49166,57358,   15, 8207,16399,24591,32783,40975
+	dw 49167,57359,   16, 8208,16400,24592,32784,40976,49168,57360,   17, 8209,16401,24593
+	dw 32785,40977,49169,57361,   18, 8210,16402,24594,32786,40978,49170,57362,   19, 8211
+	dw 16403,24595,32787,40979,49171,57363,   20, 8212,16404,24596,32788,40980,49172,57364
+	dw    21, 8213,16405,24597,32789,40981,49173,57365,   22, 8214,16406,24598,32790,40982
+	dw 49174,57366,   23, 8215,16407,24599,32791,40983,49175,57367,   24, 8216,16408,24600
+	dw 32792,40984,49176,57368,   25, 8217,16409,24601,32793,40985,49177,57369,   26, 8218
+	dw 16410,24602,32794,40986,49178,57370,   27, 8219,16411,24603,32795,40987,49179,57371
+	dw    28, 8220,16412,24604,32796,40988,49180,57372,   29, 8221,16413,24605,32797,40989
+	dw 49181,57373,   30, 8222,16414,24606,32798,40990,49182,57374,   31, 8223,16415,24607
+	dw 32799,40991,49183,57375
+
+LABEL shiftdata4 WORD
+	dw     0, 4096, 8192,12288,16384,20480,24576,28672,32768,36864,40960,45056,49152,53248
+	dw 57344,61440,    1, 4097, 8193,12289,16385,20481,24577,28673,32769,36865,40961,45057
+	dw 49153,53249,57345,61441,    2, 4098, 8194,12290,16386,20482,24578,28674,32770,36866
+	dw 40962,45058,49154,53250,57346,61442,    3, 4099, 8195,12291,16387,20483,24579,28675
+	dw 32771,36867,40963,45059,49155,53251,57347,61443,    4, 4100, 8196,12292,16388,20484
+	dw 24580,28676,32772,36868,40964,45060,49156,53252,57348,61444,    5, 4101, 8197,12293
+	dw 16389,20485,24581,28677,32773,36869,40965,45061,49157,53253,57349,61445,    6, 4102
+	dw  8198,12294,16390,20486,24582,28678,32774,36870,40966,45062,49158,53254,57350,61446
+	dw     7, 4103, 8199,12295,16391,20487,24583,28679,32775,36871,40967,45063,49159,53255
+	dw 57351,61447,    8, 4104, 8200,12296,16392,20488,24584,28680,32776,36872,40968,45064
+	dw 49160,53256,57352,61448,    9, 4105, 8201,12297,16393,20489,24585,28681,32777,36873
+	dw 40969,45065,49161,53257,57353,61449,   10, 4106, 8202,12298,16394,20490,24586,28682
+	dw 32778,36874,40970,45066,49162,53258,57354,61450,   11, 4107, 8203,12299,16395,20491
+	dw 24587,28683,32779,36875,40971,45067,49163,53259,57355,61451,   12, 4108, 8204,12300
+	dw 16396,20492,24588,28684,32780,36876,40972,45068,49164,53260,57356,61452,   13, 4109
+	dw  8205,12301,16397,20493,24589,28685,32781,36877,40973,45069,49165,53261,57357,61453
+	dw    14, 4110, 8206,12302,16398,20494,24590,28686,32782,36878,40974,45070,49166,53262
+	dw 57358,61454,   15, 4111, 8207,12303,16399,20495,24591,28687,32783,36879,40975,45071
+	dw 49167,53263,57359,61455
+
+LABEL shiftdata5 WORD
+	dw     0, 2048, 4096, 6144, 8192,10240,12288,14336,16384,18432,20480,22528,24576,26624
+	dw 28672,30720,32768,34816,36864,38912,40960,43008,45056,47104,49152,51200,53248,55296
+	dw 57344,59392,61440,63488,    1, 2049, 4097, 6145, 8193,10241,12289,14337,16385,18433
+	dw 20481,22529,24577,26625,28673,30721,32769,34817,36865,38913,40961,43009,45057,47105
+	dw 49153,51201,53249,55297,57345,59393,61441,63489,    2, 2050, 4098, 6146, 8194,10242
+	dw 12290,14338,16386,18434,20482,22530,24578,26626,28674,30722,32770,34818,36866,38914
+	dw 40962,43010,45058,47106,49154,51202,53250,55298,57346,59394,61442,63490,    3, 2051
+	dw  4099, 6147, 8195,10243,12291,14339,16387,18435,20483,22531,24579,26627,28675,30723
+	dw 32771,34819,36867,38915,40963,43011,45059,47107,49155,51203,53251,55299,57347,59395
+	dw 61443,63491,    4, 2052, 4100, 6148, 8196,10244,12292,14340,16388,18436,20484,22532
+	dw 24580,26628,28676,30724,32772,34820,36868,38916,40964,43012,45060,47108,49156,51204
+	dw 53252,55300,57348,59396,61444,63492,    5, 2053, 4101, 6149, 8197,10245,12293,14341
+	dw 16389,18437,20485,22533,24581,26629,28677,30725,32773,34821,36869,38917,40965,43013
+	dw 45061,47109,49157,51205,53253,55301,57349,59397,61445,63493,    6, 2054, 4102, 6150
+	dw  8198,10246,12294,14342,16390,18438,20486,22534,24582,26630,28678,30726,32774,34822
+	dw 36870,38918,40966,43014,45062,47110,49158,51206,53254,55302,57350,59398,61446,63494
+	dw     7, 2055, 4103, 6151, 8199,10247,12295,14343,16391,18439,20487,22535,24583,26631
+	dw 28679,30727,32775,34823,36871,38919,40967,43015,45063,47111,49159,51207,53255,55303
+	dw 57351,59399,61447,63495
+
+LABEL shiftdata6 WORD
+	dw     0, 1024, 2048, 3072, 4096, 5120, 6144, 7168, 8192, 9216,10240,11264,12288,13312
+	dw 14336,15360,16384,17408,18432,19456,20480,21504,22528,23552,24576,25600,26624,27648
+	dw 28672,29696,30720,31744,32768,33792,34816,35840,36864,37888,38912,39936,40960,41984
+	dw 43008,44032,45056,46080,47104,48128,49152,50176,51200,52224,53248,54272,55296,56320
+	dw 57344,58368,59392,60416,61440,62464,63488,64512,    1, 1025, 2049, 3073, 4097, 5121
+	dw  6145, 7169, 8193, 9217,10241,11265,12289,13313,14337,15361,16385,17409,18433,19457
+	dw 20481,21505,22529,23553,24577,25601,26625,27649,28673,29697,30721,31745,32769,33793
+	dw 34817,35841,36865,37889,38913,39937,40961,41985,43009,44033,45057,46081,47105,48129
+	dw 49153,50177,51201,52225,53249,54273,55297,56321,57345,58369,59393,60417,61441,62465
+	dw 63489,64513,    2, 1026, 2050, 3074, 4098, 5122, 6146, 7170, 8194, 9218,10242,11266
+	dw 12290,13314,14338,15362,16386,17410,18434,19458,20482,21506,22530,23554,24578,25602
+	dw 26626,27650,28674,29698,30722,31746,32770,33794,34818,35842,36866,37890,38914,39938
+	dw 40962,41986,43010,44034,45058,46082,47106,48130,49154,50178,51202,52226,53250,54274
+	dw 55298,56322,57346,58370,59394,60418,61442,62466,63490,64514,    3, 1027, 2051, 3075
+	dw  4099, 5123, 6147, 7171, 8195, 9219,10243,11267,12291,13315,14339,15363,16387,17411
+	dw 18435,19459,20483,21507,22531,23555,24579,25603,26627,27651,28675,29699,30723,31747
+	dw 32771,33795,34819,35843,36867,37891,38915,39939,40963,41987,43011,44035,45059,46083
+	dw 47107,48131,49155,50179,51203,52227,53251,54275,55299,56323,57347,58371,59395,60419
+	dw 61443,62467,63491,64515
+
+LABEL shiftdata7 WORD
+	dw     0,  512, 1024, 1536, 2048, 2560, 3072, 3584, 4096, 4608, 5120, 5632, 6144, 6656
+	dw  7168, 7680, 8192, 8704, 9216, 9728,10240,10752,11264,11776,12288,12800,13312,13824
+	dw 14336,14848,15360,15872,16384,16896,17408,17920,18432,18944,19456,19968,20480,20992
+	dw 21504,22016,22528,23040,23552,24064,24576,25088,25600,26112,26624,27136,27648,28160
+	dw 28672,29184,29696,30208,30720,31232,31744,32256,32768,33280,33792,34304,34816,35328
+	dw 35840,36352,36864,37376,37888,38400,38912,39424,39936,40448,40960,41472,41984,42496
+	dw 43008,43520,44032,44544,45056,45568,46080,46592,47104,47616,48128,48640,49152,49664
+	dw 50176,50688,51200,51712,52224,52736,53248,53760,54272,54784,55296,55808,56320,56832
+	dw 57344,57856,58368,58880,59392,59904,60416,60928,61440,61952,62464,62976,63488,64000
+	dw 64512,65024,    1,  513, 1025, 1537, 2049, 2561, 3073, 3585, 4097, 4609, 5121, 5633
+	dw  6145, 6657, 7169, 7681, 8193, 8705, 9217, 9729,10241,10753,11265,11777,12289,12801
+	dw 13313,13825,14337,14849,15361,15873,16385,16897,17409,17921,18433,18945,19457,19969
+	dw 20481,20993,21505,22017,22529,23041,23553,24065,24577,25089,25601,26113,26625,27137
+	dw 27649,28161,28673,29185,29697,30209,30721,31233,31745,32257,32769,33281,33793,34305
+	dw 34817,35329,35841,36353,36865,37377,37889,38401,38913,39425,39937,40449,40961,41473
+	dw 41985,42497,43009,43521,44033,44545,45057,45569,46081,46593,47105,47617,48129,48641
+	dw 49153,49665,50177,50689,51201,51713,52225,52737,53249,53761,54273,54785,55297,55809
+	dw 56321,56833,57345,57857,58369,58881,59393,59905,60417,60929,61441,61953,62465,62977
+	dw 63489,64001,64513,65025
+
+shifttabletable	dw	shiftdata0,shiftdata1,shiftdata2,shiftdata3
+		dw	shiftdata4,shiftdata5,shiftdata6,shiftdata7
+
+PUBLIC	shifttabletable
+
+
+;============================================================================
+
+CODESEG
+
+IFE GRMODE-CGAGR
+INCLUDE	"ID_VW_AC.ASM"
+ENDIF
+
+IFE GRMODE-EGAGR
+INCLUDE	"ID_VW_AE.ASM"
+ENDIF
+
+IFE GRMODE-VGAGR
+INCLUDE	"ID_VW_AV.ASM"
+ENDIF
+
+;============================================================================
+;
+;                           MISC VIDEO ROUTINES
+;
+;============================================================================
+
+;========
+;
+; VW_WaitVBL (int number)
+;
+;========
+
+PROC	VW_WaitVBL number:WORD
+PUBLIC	VW_WaitVBL
+
+if WAITFORVBL				; skip wait if profiling
+
+	mov	dx,STATUS_REGISTER_1
+
+	mov	cx,[number]
+
+waitvbl1:
+	in	al,dx
+	test	al,00001000b	;look for vbl
+	jnz	waitvbl1
+
+waitvbl2:
+	in	al,dx
+	test	al,00001000b	;look for vbl
+	jz	waitvbl2
+
+	loop	waitvbl1
+
+endif
+
+	ret
+
+ENDP
+
+
+;===========================================================================
+
+
+	MASM
+;ÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍ
+;
+; Name:	VW_VideoID
+;
+; Function:	Detects the presence of various video subsystems
+;
+; int VideoID;
+;
+; Subsystem ID values:
+; 	 0  = (none)
+; 	 1  = MDA
+; 	 2  = CGA
+; 	 3  = EGA
+; 	 4  = MCGA
+; 	 5  = VGA
+; 	80h = HGC
+; 	81h = HGC+
+; 	82h = Hercules InColor
+;
+;ÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍ
+
+;ÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍ
+;
+; Equates
+;
+;ÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍ
+VIDstruct	STRUC		; corresponds to C data structure
+
+Video0Type	DB	?	; first subsystem type
+Display0Type	DB	? 	; display attached to first subsystem
+
+Video1Type	DB	?	; second subsystem type
+Display1Type	DB	?	; display attached to second subsystem
+
+VIDstruct	ENDS
+
+
+Device0	EQU	word ptr Video0Type[di]
+Device1	EQU	word ptr Video1Type[di]
+
+
+MDA	EQU	1	; subsystem types
+CGA	EQU	2
+EGA	EQU	3
+MCGA	EQU	4
+VGA	EQU	5
+HGC	EQU	80h
+HGCPlus	EQU	81h
+InColor	EQU	82h
+
+MDADisplay	EQU	1	; display types
+CGADisplay	EQU	2
+EGAColorDisplay	EQU	3
+PS2MonoDisplay	EQU	4
+PS2ColorDisplay	EQU	5
+
+TRUE	EQU	1
+FALSE	EQU	0
+
+;ÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍ
+;
+; Program
+;
+;ÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍ
+
+Results	VIDstruct <>	;results go here!
+
+EGADisplays	DB	CGADisplay	; 0000b, 0001b	(EGA switch values)
+	DB	EGAColorDisplay	; 0010b, 0011b
+	DB	MDADisplay	; 0100b, 0101b
+	DB	CGADisplay	; 0110b, 0111b
+	DB	EGAColorDisplay	; 1000b, 1001b
+	DB	MDADisplay	; 1010b, 1011b
+
+DCCtable	DB	0,0	; translate table for INT 10h func 1Ah
+	DB	MDA,MDADisplay
+	DB	CGA,CGADisplay
+	DB	0,0
+	DB	EGA,EGAColorDisplay
+	DB	EGA,MDADisplay
+	DB	0,0
+	DB	VGA,PS2MonoDisplay
+	DB	VGA,PS2ColorDisplay
+	DB	0,0
+	DB	MCGA,EGAColorDisplay
+	DB	MCGA,PS2MonoDisplay
+	DB	MCGA,PS2ColorDisplay
+
+TestSequence	DB	TRUE	; this list of flags and addresses
+	DW	FindPS2	;  determines the order in which this
+			;  program looks for the various
+EGAflag	DB	?	;  subsystems
+	DW	FindEGA
+
+CGAflag	DB	?
+	DW	FindCGA
+
+Monoflag	DB	?
+	DW	FindMono
+
+NumberOfTests	EQU	($-TestSequence)/3
+
+
+PUBLIC	VW_VideoID
+VW_VideoID	PROC
+
+	push	bp	; preserve caller registers
+	mov	bp,sp
+	push	ds
+	push	si
+	push	di
+
+	push	cs
+	pop	ds
+	ASSUME	DS:@Code
+
+; initialize the data structure that will contain the results
+
+	lea	di,Results	; DS:DI -> start of data structure
+
+	mov	Device0,0	; zero these variables
+	mov	Device1,0
+
+; look for the various subsystems using the subroutines whose addresses are
+; tabulated in TestSequence; each subroutine sets flags in TestSequence
+; to indicate whether subsequent subroutines need to be called
+
+	mov	byte ptr CGAflag,TRUE
+	mov	byte ptr EGAflag,TRUE
+	mov	byte ptr Monoflag,TRUE
+
+	mov	cx,NumberOfTests
+	mov	si,offset TestSequence
+
+@@L01:	lodsb		; AL := flag
+	test	al,al
+	lodsw		; AX := subroutine address
+	jz	@@L02	; skip subroutine if flag is false
+
+	push	si
+	push	cx
+	call	ax	; call subroutine to detect subsystem
+	pop	cx
+	pop	si
+
+@@L02:	loop	@@L01
+
+; determine which subsystem is active
+
+	call	FindActive
+
+	mov	al,Results.Video0Type
+	mov	ah,0	; was:  Results.Display0Type
+
+	pop	di	; restore caller registers and return
+	pop	si
+	pop	ds
+	mov	sp,bp
+	pop	bp
+	ret
+
+VW_VideoID	ENDP
+
+
+;
+; FindPS2
+;
+; This subroutine uses INT 10H function 1Ah to determine the video BIOS
+; Display Combination Code (DCC) for each video subsystem present.
+;
+
+FindPS2	PROC	near
+
+	mov	ax,1A00h
+	int	10h	; call video BIOS for info
+
+	cmp	al,1Ah
+	jne	@@L13	; exit if function not supported (i.e.,
+			;  no MCGA or VGA in system)
+
+; convert BIOS DCCs into specific subsystems & displays
+
+	mov	cx,bx
+	xor	bh,bh	; BX := DCC for active subsystem
+
+	or	ch,ch
+	jz	@@L11	; jump if only one subsystem present
+
+	mov	bl,ch	; BX := inactive DCC
+	add	bx,bx
+	mov	ax,[bx+offset DCCtable]
+
+	mov	Device1,ax
+
+	mov	bl,cl
+	xor	bh,bh	; BX := active DCC
+
+@@L11:	add	bx,bx
+	mov	ax,[bx+offset DCCtable]
+
+	mov	Device0,ax
+
+; reset flags for subsystems that have been ruled out
+
+	mov	byte ptr CGAflag,FALSE
+	mov	byte ptr EGAflag,FALSE
+	mov	byte ptr Monoflag,FALSE
+
+	lea	bx,Video0Type[di]  ; if the BIOS reported an MDA ...
+	cmp	byte ptr [bx],MDA
+	je	@@L12
+
+	lea	bx,Video1Type[di]
+	cmp	byte ptr [bx],MDA
+	jne	@@L13
+
+@@L12:	mov	word ptr [bx],0    ; ... Hercules can't be ruled out
+	mov	byte ptr Monoflag,TRUE
+
+@@L13:	ret
+
+FindPS2	ENDP
+
+
+;
+; FindEGA
+;
+; Look for an EGA.  This is done by making a call to an EGA BIOS function
+;  which doesn't exist in the default (MDA, CGA) BIOS.
+
+FindEGA	PROC	near	; Caller:	AH = flags
+			; Returns:	AH = flags
+			;		Video0Type and
+			;		 Display0Type updated
+
+	mov	bl,10h	; BL := 10h (return EGA info)
+	mov	ah,12h	; AH := INT 10H function number
+	int	10h	; call EGA BIOS for info
+			; if EGA BIOS is present,
+			;  BL <> 10H
+			;  CL = switch setting
+	cmp	bl,10h
+	je	@@L22	; jump if EGA BIOS not present
+
+	mov	al,cl
+	shr	al,1	; AL := switches/2
+	mov	bx,offset EGADisplays
+	xlat		; determine display type from switches
+	mov	ah,al	; AH := display type
+	mov	al,EGA	; AL := subystem type
+	call	FoundDevice
+
+	cmp	ah,MDADisplay
+	je	@@L21	; jump if EGA has a monochrome display
+
+	mov	CGAflag,FALSE	; no CGA if EGA has color display
+	jmp	short @@L22
+
+@@L21:	mov	Monoflag,FALSE	; EGA has a mono display, so MDA and
+			;  Hercules are ruled out
+@@L22:	ret
+
+FindEGA	ENDP
+
+;
+; FindCGA
+;
+; This is done by looking for the CGA's 6845 CRTC at I/O port 3D4H.
+;
+FindCGA	PROC	near	; Returns:	VIDstruct updated
+
+	mov	dx,3D4h	; DX := CRTC address port
+	call	Find6845
+	jc	@@L31	; jump if not present
+
+	mov	al,CGA
+	mov	ah,CGADisplay
+	call	FoundDevice
+
+@@L31:	ret
+
+FindCGA	ENDP
+
+;
+; FindMono
+;
+; This is done by looking for the MDA's 6845 CRTC at I/O port 3B4H.  If
+; a 6845 is found, the subroutine distinguishes between an MDA
+; and a Hercules adapter by monitoring bit 7 of the CRT Status byte.
+; This bit changes on Hercules adapters but does not change on an MDA.
+;
+; The various Hercules adapters are identified by bits 4 through 6 of
+; the CRT Status value:
+;
+; 000b = HGC
+; 001b = HGC+
+; 101b = InColor card
+;
+
+FindMono	PROC	near	; Returns:	VIDstruct updated
+
+	mov	dx,3B4h	; DX := CRTC address port
+	call	Find6845
+	jc	@@L44	; jump if not present
+
+	mov	dl,0BAh	; DX := 3BAh (status port)
+	in	al,dx
+	and	al,80h
+	mov	ah,al	; AH := bit 7 (vertical sync on HGC)
+
+	mov	cx,8000h	; do this 32768 times
+@@L41:	in	al,dx
+	and	al,80h	; isolate bit 7
+	cmp	ah,al
+	loope	@@L41	; wait for bit 7 to change
+	jne	@@L42	; if bit 7 changed, it's a Hercules
+
+	mov	al,MDA	; if bit 7 didn't change, it's an MDA
+	mov	ah,MDADisplay
+	call	FoundDevice
+	jmp	short @@L44
+
+@@L42:	in	al,dx
+	mov	dl,al	; DL := value from status port
+	and	dl,01110000b	; mask bits 4 thru 6
+
+	mov	ah,MDADisplay	; assume it's a monochrome display
+
+	mov	al,HGCPlus	; look for an HGC+
+	cmp	dl,00010000b
+	je	@@L43	; jump if it's an HGC+
+
+	mov	al,HGC	; look for an InColor card or HGC
+	cmp	dl,01010000b
+	jne	@@L43	; jump if it's not an InColor card
+
+	mov	al,InColor	; it's an InColor card
+	mov	ah,EGAColorDisplay
+
+@@L43:	call	FoundDevice
+
+@@L44:	ret
+
+FindMono	ENDP
+
+;
+; Find6845
+;
+; This routine detects the presence of the CRTC on a MDA, CGA or HGC.
+; The technique is to write and read register 0Fh of the chip (cursor
+; low).  If the same value is read as written, assume the chip is
+; present at the specified port addr.
+;
+
+Find6845	PROC	near	; Caller:  DX = port addr
+			; Returns: cf set if not present
+	mov	al,0Fh
+	out	dx,al	; select 6845 reg 0Fh (Cursor Low)
+	inc	dx
+	in	al,dx	; AL := current Cursor Low value
+	mov	ah,al	; preserve in AH
+	mov	al,66h	; AL := arbitrary value
+	out	dx,al	; try to write to 6845
+
+	mov	cx,100h
+@@L51:	loop	@@L51	; wait for 6845 to respond
+
+	in	al,dx
+	xchg	ah,al	; AH := returned value
+			; AL := original value
+	out	dx,al	; restore original value
+
+	cmp	ah,66h	; test whether 6845 responded
+	je	@@L52	; jump if it did (cf is reset)
+
+	stc		; set carry flag if no 6845 present
+
+@@L52:	ret
+
+Find6845	ENDP
+
+
+;
+; FindActive
+;
+; This subroutine stores the currently active device as Device0.  The
+; current video mode determines which subsystem is active.
+;
+
+FindActive	PROC	near
+
+	cmp	word ptr Device1,0
+	je	@@L63	; exit if only one subsystem
+
+	cmp	Video0Type[di],4	; exit if MCGA or VGA present
+	jge	@@L63	;  (INT 10H function 1AH
+	cmp	Video1Type[di],4	;  already did the work)
+	jge	@@L63
+
+	mov	ah,0Fh
+	int	10h	; AL := current BIOS video mode
+
+	and	al,7
+	cmp	al,7	; jump if monochrome
+	je	@@L61	;  (mode 7 or 0Fh)
+
+	cmp	Display0Type[di],MDADisplay
+	jne	@@L63	; exit if Display0 is color
+	jmp	short @@L62
+
+@@L61:	cmp	Display0Type[di],MDADisplay
+	je	@@L63	; exit if Display0 is monochrome
+
+@@L62:	mov	ax,Device0	; make Device0 currently active
+	xchg	ax,Device1
+	mov	Device0,ax
+
+@@L63:	ret
+
+FindActive	ENDP
+
+
+;
+; FoundDevice
+;
+; This routine updates the list of subsystems.
+;
+
+FoundDevice	PROC	near	; Caller:    AH = display #
+			;	     AL = subsystem #
+			; Destroys:  BX
+	lea	bx,Video0Type[di]
+	cmp	byte ptr [bx],0
+	je	@@L71	; jump if 1st subsystem
+
+	lea	bx,Video1Type[di]	; must be 2nd subsystem
+
+@@L71:	mov	[bx],ax	; update list entry
+	ret
+
+FoundDevice	ENDP
+
+IDEAL
+
+
+
+END
diff --git a/16/keen456/KEEN4-6/ID_VW_AC.ASM b/16/keen456/KEEN4-6/ID_VW_AC.ASM
new file mode 100755
index 00000000..80523b4b
--- /dev/null
+++ b/16/keen456/KEEN4-6/ID_VW_AC.ASM
@@ -0,0 +1,1536 @@
+; Reconstructed Commander Keen 4-6 Source Code
+; Copyright (C) 2021 K1n9_Duk3
+;
+; This file is primarily based on:
+; Catacomb 3-D Source Code
+; Copyright (C) 1993-2014 Flat Rock Software
+;
+; This program is free software; you can redistribute it and/or modify
+; it under the terms of the GNU General Public License as published by
+; the Free Software Foundation; either version 2 of the License, or
+; (at your option) any later version.
+;
+; This program is distributed in the hope that it will be useful,
+; but WITHOUT ANY WARRANTY; without even the implied warranty of
+; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+; GNU General Public License for more details.
+;
+; You should have received a copy of the GNU General Public License along
+; with this program; if not, write to the Free Software Foundation, Inc.,
+; 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+
+;=================================
+;
+; CGA view manager routines
+;
+;=================================
+
+;============================================================================
+;
+; All of these routines draw into a floating virtual screen segment in main
+; memory.  bufferofs points to the origin of the drawing page in screenseg.
+; The routines that write out words must take into account buffer wrapping
+; and not write a word at 0xffff (which causes an exception on 386s).
+;
+; The direction flag should be clear
+;
+;============================================================================
+
+DATASEG
+
+plotpixels	db	0c0h,030h,0ch,03h
+colorbyte	db	000000b,01010101b,10101010b,11111111b
+colorword	dw	0,5555h,0aaaah,0ffffh
+
+CODESEG
+
+;============================================================================
+;
+; VW_Plot (int x,y,color)
+;
+;============================================================================
+
+
+PROC	VW_Plot x:WORD, y:WORD, color:WORD
+PUBLIC	VW_Plot
+USES	SI,DI
+
+	mov	es,[screenseg]
+
+	mov	di,[bufferofs]
+	mov	bx,[y]
+	shl	bx,1
+	add	di,[ylookup+bx]
+	mov	bx,[x]
+	mov	ax,bx
+	shr	ax,1
+	shr	ax,1
+	add	di,ax				; di = byte on screen
+
+	and	bx,3
+	mov	ah,[plotpixels+bx]
+	mov	bx,[color]
+	mov	cl,[colorbyte+bx]
+	and	cl,ah
+	not	ah
+
+	mov	al,[es:di]
+	and	al,ah				; mask off other pixels
+	or	al,cl
+	stosb
+
+	ret
+
+ENDP
+
+
+;============================================================================
+;
+; VW_Vlin (int yl,yh,x,color)
+;
+;============================================================================
+
+PROC	VW_Vlin yl:WORD, yh:WORD, x:WORD, color:WORD
+PUBLIC	VW_Vlin
+USES	SI,DI
+
+	mov	es,[screenseg]
+
+	mov	di,[bufferofs]
+	mov	bx,[yl]
+	shl	bx,1
+	add	di,[ylookup+bx]
+	mov	bx,[x]
+	mov	ax,bx
+	shr	ax,1
+	shr	ax,1
+	add	di,ax				; di = byte on screen
+
+	and	bx,3
+	mov	ah,[plotpixels+bx]
+	mov	bx,[color]
+	mov	bl,[colorbyte+bx]
+	and	bl,ah
+	not	ah
+
+	mov	cx,[yh]
+	sub	cx,[yl]
+	inc	cx					;number of pixels to plot
+
+	mov	dx,[linewidth]
+
+@@plot:
+	mov	al,[es:di]
+	and	al,ah				; mask off other pixels
+	or	al,bl
+	mov [es:di],al
+	add	di,dx
+	loop	@@plot
+
+	ret
+
+	ret
+
+ENDP
+
+
+;============================================================================
+
+
+;===================
+;
+; VW_DrawTile8
+;
+; xcoord in bytes (8 pixels), ycoord in pixels
+; All Tile8s are in one grseg, so an offset is calculated inside it
+;
+; DONE
+;
+;===================
+
+PROC	VW_DrawTile8	xcoord:WORD, ycoord:WORD, tile:WORD
+PUBLIC	VW_DrawTile8
+USES	SI,DI
+
+	mov	es,[screenseg]
+
+	mov	di,[bufferofs]
+	add	di,[xcoord]
+	mov	bx,[ycoord]
+	shl	bx,1
+	add	di,[ylookup+bx]
+
+	mov	bx,[linewidth]
+	sub	bx,2
+
+	mov	si,[tile]
+	shl	si,1
+	shl	si,1
+	shl	si,1
+	shl	si,1
+
+	mov	ds,[grsegs+STARTTILE8*2] ; segment for all tile8s
+
+;
+; start drawing
+;
+
+REPT	7
+	movsb						;no word moves because of segment wrapping
+	movsb
+	add	di,bx
+ENDM
+	movsb
+	movsb
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+ENDP
+
+
+;============================================================================
+;
+; VW_MaskBlock
+;
+; Draws a masked block shape to the screen.  bufferofs is NOT accounted for.
+; The mask comes first, then the data.  Seperate unwound routines are used
+; to speed drawing.
+;
+; Mask blocks will allways be an even width because of the way IGRAB works
+;
+; DONE
+;
+;============================================================================
+
+DATASEG
+
+UNWOUNDMASKS	=	18
+
+
+maskroutines	dw	mask0,mask0,mask2E,mask2O,mask4E,mask4O
+				dw	mask6E,mask6O,mask8E,mask8O,mask10E,mask10O
+				dw	mask12E,mask12O,mask14E,mask14O,mask16E,mask16O
+				dw	mask18E,mask18O
+
+
+routinetouse	dw	?
+
+CODESEG
+
+PROC	VW_MaskBlock	segm:WORD, ofs:WORD, dest:WORD, wide:WORD, height:WORD, planesize:WORD
+PUBLIC	VW_MaskBlock
+USES	SI,DI
+
+	mov	es,[screenseg]
+
+	mov	di,[wide]
+	mov	dx,[linewidth]
+	sub	dx,di					;dx = delta to start of next line
+
+	mov	bx,[planesize]			; si+bx = data location
+
+	cmp	di,UNWOUNDMASKS
+	jbe	@@unwoundroutine
+
+;==============
+;
+; General purpose masked block drawing.  This could be optimised into
+; four routines to use words, but few play loop sprites should be this big!
+;
+;==============
+
+	mov	[ss:linedelta],dx
+	mov	ds,[segm]
+	mov	si,[ofs]
+	mov	di,[dest]
+	mov	dx,[height]				;scan lines to draw
+
+@@lineloopgen:
+	mov	cx,[wide]
+@@byteloop:
+	mov	al,[es:di]
+	and	al,[si]
+	or	al,[bx+si]
+	inc	si
+	stosb
+	loop	@@byteloop
+
+	add	di,[ss:linedelta]
+	dec	dx
+	jnz	@@lineloopgen
+
+mask0:
+	mov	ax,ss
+	mov	ds,ax
+	ret							;width of 0 = no drawing
+
+
+;=================
+;
+; use the unwound routines
+;
+;=================
+
+@@unwoundroutine:
+	shr	di,1					;we only have even width unwound routines
+	mov	cx,[dest]
+	shr	cx,1
+	rcl	di,1					;shift a 1 in if destination is odd
+	shl	di,1
+	mov	ax,[maskroutines+di]	;call the right routine
+
+	mov	ds,[segm]
+	mov	si,[ofs]
+	mov	di,[dest]
+	mov	cx,[height]				;scan lines to draw
+
+	jmp ax						;draw it
+
+;=================
+;
+; Horizontally unwound routines to draw certain masked blocks faster
+;
+;=================
+
+MACRO	MASKBYTE
+	mov	al,[es:di]
+	and	al,[si]
+	or	al,[bx+si]
+	inc	si
+	stosb
+ENDM
+
+MACRO	MASKWORD
+	mov	ax,[es:di]
+	and	ax,[si]
+	or	ax,[bx+si]
+	inc	si
+	inc	si
+	stosw
+ENDM
+
+MACRO	SPRITELOOP	addr
+	add	di,dx
+	loop	addr
+	mov	ax,ss
+	mov	ds,ax
+	ret
+ENDM
+
+
+EVEN
+mask2E:
+	MASKWORD
+	SPRITELOOP	mask2E
+
+EVEN
+mask2O:
+	MASKBYTE
+	MASKBYTE
+	SPRITELOOP	mask2O
+
+EVEN
+mask4E:
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask4E
+
+EVEN
+mask4O:
+	MASKBYTE
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask4O
+
+EVEN
+mask6E:
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask6E
+
+EVEN
+mask6O:
+	MASKBYTE
+	MASKWORD
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask6O
+
+EVEN
+mask8E:
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask8E
+
+EVEN
+mask8O:
+	MASKBYTE
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask8O
+
+EVEN
+mask10E:
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask10E
+
+EVEN
+mask10O:
+	MASKBYTE
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask10O
+
+EVEN
+mask12E:
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask12E
+
+EVEN
+mask12O:
+	MASKBYTE
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask12O
+
+EVEN
+mask14E:
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask14E
+
+EVEN
+mask14O:
+	MASKBYTE
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask14O
+
+EVEN
+mask16E:
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask16E
+
+EVEN
+mask16O:
+	MASKBYTE
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask16O
+
+EVEN
+mask18E:
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask18E
+
+EVEN
+mask18O:
+	MASKBYTE
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask18O
+
+
+ENDP
+
+
+;============================================================================
+;
+; VW_InverseMask
+;
+; Draws a masked block shape to the screen.  bufferofs is NOT accounted for.
+; The mask comes first, then the data.
+;
+; Mask blocks will allways be an even width because of the way IGRAB works
+;
+;============================================================================
+
+PROC	VW_InverseMask	segm:WORD, ofs:WORD, dest:WORD, wide:WORD, height:WORD
+PUBLIC	VW_InverseMask
+USES	SI,DI
+
+	mov	es, [screenseg]
+	mov	ax, [wide]
+	mov	dx, [linewidth]
+	sub	dx, ax;
+	mov	ds, [segm]
+	mov	si, [ofs]
+	mov	di, [dest]
+	mov	bx, [height]
+	shr	[wide], 1
+@@yloop:
+	mov	cx, [wide]
+@@xloop:
+	lodsw
+	not	ax
+	or	[es:di], ax
+	inc	di
+	inc	di
+	loop	@@xloop
+	add	di, dx
+	dec	bx
+	jnz	@@yloop
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+ENDP
+
+
+;============================================================================
+;
+; VW_ScreenToScreen
+;
+; Basic block copy routine.  Copies one block of screen memory to another,
+; bufferofs is NOT accounted for.
+;
+; DONE
+;
+;============================================================================
+
+PROC	VW_ScreenToScreen	source:WORD, dest:WORD, wide:WORD, height:WORD
+PUBLIC	VW_ScreenToScreen
+USES	SI,DI
+
+	mov	bx,[linewidth]
+	sub	bx,[wide]
+
+	mov	ax,[screenseg]
+	mov	es,ax
+	mov	ds,ax
+
+	mov	si,[source]
+	mov	di,[dest]				;start at same place in all planes
+	mov	dx,[height]				;scan lines to draw
+	mov	ax,[wide]
+;
+; if the width, source, and dest are all even, use word moves
+; This is allways the case in the CGA refresh
+;
+	test	ax,1
+	jnz	@@bytelineloop
+	test	si,1
+	jnz	@@bytelineloop
+	test	di,1
+	jnz	@@bytelineloop
+
+	shr	ax,1
+@@wordlineloop:
+	mov	cx,ax
+	rep	movsw
+	add	si,bx
+	add	di,bx
+
+	dec	dx
+	jnz	@@wordlineloop
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+@@bytelineloop:
+	mov	cx,ax
+	rep	movsb
+	add	si,bx
+	add	di,bx
+
+	dec	dx
+	jnz	@@bytelineloop
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+ENDP
+
+
+;============================================================================
+;
+; VW_MemToScreen
+;
+; Basic block drawing routine. Takes a block shape at segment pointer source
+; of width by height data, and draws it to dest in the virtual screen,
+; based on linewidth.  bufferofs is NOT accounted for.
+; There are four drawing routines to provide the best optimized code while
+; accounting for odd segment wrappings due to the floating screens.
+;
+; DONE
+;
+;============================================================================
+
+DATASEG
+
+memtoscreentable	dw	eventoeven,eventoodd,oddtoeven,oddtoodd
+
+CODESEG
+
+
+PROC	VW_MemToScreen	source:WORD, dest:WORD, wide:WORD, height:WORD
+PUBLIC	VW_MemToScreen
+USES	SI,DI
+
+	mov	es,[screenseg]
+
+	mov	bx,[linewidth]
+	sub	bx,[wide]
+
+	mov	ds,[source]
+
+	xor	si,si					;block is segment aligned
+
+	xor	di,di
+	shr	[wide],1				;change wide to words, and see if carry is set
+	rcl	di,1					;1 if wide is odd
+	mov	ax,[dest]
+	shr	ax,1
+	rcl	di,1					;shift a 1 in if destination is odd
+	shl	di,1					;to index into a word width table
+	mov	dx,[height]				;scan lines to draw
+	mov	ax,[wide]
+	jmp	[ss:memtoscreentable+di]	;call the right routine
+
+;==============
+;
+; Copy an even width block to an even destination address
+;
+;==============
+
+eventoeven:
+	mov	di,[dest]				;start at same place in all planes
+EVEN
+@@lineloopEE:
+	mov	cx,ax
+	rep	movsw
+	add	di,bx
+	dec	dx
+	jnz	@@lineloopEE
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+;==============
+;
+; Copy an odd width block to an even video address
+;
+;==============
+
+oddtoeven:
+	mov	di,[dest]				;start at same place in all planes
+EVEN
+@@lineloopOE:
+	mov	cx,ax
+	rep	movsw
+	movsb						;copy the last byte
+	add	di,bx
+	dec	dx
+	jnz	@@lineloopOE
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+;==============
+;
+; Copy an even width block to an odd video address
+;
+;==============
+
+eventoodd:
+	mov	di,[dest]				;start at same place in all planes
+	dec	ax						;one word has to be handled seperately
+EVEN
+@@lineloopEO:
+	movsb
+	mov	cx,ax
+	rep	movsw
+	movsb
+	add	di,bx
+	dec	dx
+	jnz	@@lineloopEO
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+;==============
+;
+; Copy an odd width block to an odd video address
+;
+;==============
+
+oddtoodd:
+	mov	di,[dest]				;start at same place in all planes
+EVEN
+@@lineloopOO:
+	movsb
+	mov	cx,ax
+	rep	movsw
+	add	di,bx
+	dec	dx
+	jnz	@@lineloopOO
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+	ret
+
+
+ENDP
+
+;===========================================================================
+;
+; VW_ScreenToMem
+;
+; Copies a block of video memory to main memory, in order from planes 0-3.
+; This could be optimized along the lines of VW_MemToScreen to take advantage
+; of word copies, but this is an infrequently called routine.
+;
+; DONE
+;
+;===========================================================================
+
+PROC	VW_ScreenToMem	source:WORD, dest:WORD, wide:WORD, height:WORD
+PUBLIC	VW_ScreenToMem
+USES	SI,DI
+
+	mov	es,[dest]
+
+	mov	bx,[linewidth]
+	sub	bx,[wide]
+
+	mov	ds,[screenseg]
+
+	xor	di,di
+
+	mov	si,[source]
+	mov	dx,[height]				;scan lines to draw
+
+@@lineloop:
+	mov	cx,[wide]
+	rep	movsb
+
+	add	si,bx
+
+	dec	dx
+	jnz	@@lineloop
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+ENDP
+
+
+;===========================================================================
+;
+;                    MISC CGA ROUTINES
+;
+;===========================================================================
+
+;==============
+;
+; VW_SetScreen
+;
+; DONE
+;
+;==============
+
+PROC	VW_SetScreen  crtc:WORD
+PUBLIC	VW_SetScreen
+
+;
+; for some reason, my XT's EGA card doesn't like word outs to the CRTC
+; index...
+;
+	cli
+
+	mov	cx,[crtc]
+	mov	dx,CRTC_INDEX
+	mov	al,0ch		;start address high register
+	out	dx,al
+	inc	dx
+	mov	al,ch
+	out	dx,al
+	dec	dx
+	mov	al,0dh		;start address low register
+	out	dx,al
+	mov	al,cl
+	inc	dx
+	out	dx,al
+
+	sti
+
+	ret
+
+ENDP
+
+
+if NUMFONT+NUMFONTM
+
+;===========================================================================
+;
+; GENERAL FONT DRAWING ROUTINES
+;
+;===========================================================================
+
+DATASEG
+
+px	dw	?					; proportional character drawing coordinates
+py	dw	?
+pdrawmode	db	11000b		; 8 = OR, 24 = XOR, put in GC_DATAROTATE
+fontcolor	db	15		;0-15 mapmask value
+
+PUBLIC	px,py,pdrawmode,fontcolor
+
+;
+; offsets in font structure
+;
+pcharheight	=	0		;lines high
+charloc		=	2		;pointers to every character
+charwidth	=	514		;every character's width in pixels
+
+
+propchar	dw	?			; the character number to shift
+stringptr	dw	?,?
+
+fontcolormask	dw	?			; font color expands into this
+
+BUFFWIDTH	=	100
+BUFFHEIGHT	=   32			; must be twice as high as font for masked fonts
+
+databuffer	db	BUFFWIDTH*BUFFHEIGHT dup (?)
+
+bufferwidth	dw	?						; bytes with valid info / line
+bufferheight dw	?						; number of lines currently used
+
+bufferbyte	dw	?
+bufferbit	dw	?
+PUBLIC	bufferwidth,bufferheight,bufferbyte,bufferbit
+
+screenspot	dw	?						; where the buffer is going
+
+bufferextra	dw	?						; add at end of a line copy
+screenextra	dw	?
+
+CODESEG
+
+;======================
+;
+; Macros to table shift a byte of font
+;
+;======================
+
+MACRO	SHIFTNOXOR
+	mov	al,[es:bx]		; source
+	xor	ah,ah
+	shl	ax,1
+	mov	si,ax
+	mov	ax,[bp+si]		; table shift into two bytes
+	or	[di],al			; or with first byte
+	inc	di
+	mov	[di],ah			; replace next byte
+	inc	bx				; next source byte
+ENDM
+
+MACRO	SHIFTWITHXOR
+	mov	al,[es:bx]		; source
+	xor	ah,ah
+	shl	ax,1
+	mov	si,ax
+	mov	ax,[bp+si]		; table shift into two bytes
+	not	ax
+	and	[di],al			; and with first byte
+	inc	di
+	mov	[di],ah			; replace next byte
+	inc	bx				; next source byte
+ENDM
+
+
+;=======================
+;
+; VWL_XORBuffer
+;
+; Pass buffer start in SI (somewhere in databuffer)
+; Draws the buffer to the screen buffer
+;
+;========================
+
+PROC	VWL_XORBuffer	NEAR
+USES	BP
+	mov	bl,[fontcolor]
+	xor	bh,bh
+	shl	bx,1
+	mov	ax,[colorword+bx]
+	mov	[fontcolormask],ax
+
+	mov	es,[screenseg]
+	mov	di,[screenspot]
+
+	mov	bx,[bufferwidth]		;calculate offsets for end of each line
+	mov	[bufferwidth],bx
+
+	or	bx,bx
+	jnz	@@isthere
+	ret							;nothing to draw
+
+@@isthere:
+	test	bx,1
+	jnz	@@odd
+	jmp	@@even
+;
+; clear the last byte so word draws can be used
+;
+@@odd:
+	mov	al,0
+line	=	0
+REPT	BUFFHEIGHT
+	mov	[BYTE databuffer+BUFFWIDTH*line+bx],al
+line	=	line+1
+ENDM
+
+	inc	bx
+@@even:
+	mov	ax,[linewidth]
+	sub	ax,bx
+	mov	[screenextra],ax
+	mov	ax,BUFFWIDTH
+	sub	ax,bx
+	mov	[bufferextra],ax
+	mov	dx,bx
+
+	mov	bx,[bufferheight]		;lines to copy
+	mov	bp,[fontcolormask]
+@@lineloop:
+	mov	cx,dx
+@@byteloop:
+	lodsb						;get a word from the buffer
+	and	ax,bp
+	xor	[es:di],al				;draw it
+	inc	di
+	loop	@@byteloop
+
+	add	si,[bufferextra]
+	add	di,[screenextra]
+
+	dec	bx
+	jnz	@@lineloop
+
+	ret
+ENDP
+
+
+DATASEG
+
+;============================================================================
+;
+; NON MASKED FONT DRAWING ROUTINES
+;
+;============================================================================
+
+if numfont
+
+DATASEG
+
+shiftdrawtable	dw      0,shift1wide,shift2wide,shift3wide,shift4wide
+				dw		shift5wide,shift6wide
+
+CODESEG
+
+;==================
+;
+; ShiftPropChar
+;
+; Call with BX = character number (0-255)
+; Draws one character to the buffer at bufferbyte/bufferbit, and adjusts
+; them to the new position
+;
+;==================
+
+PROC	ShiftPropChar	NEAR
+
+	mov	si,[fontnumber]
+	shl	si,1
+	mov	es,[grsegs+STARTFONT*2+si]	;segment of font to use
+
+;
+; find character location, width, and height
+;
+	mov	si,[es:charwidth+bx]
+	and	si,0ffh					;SI hold width in pixels
+	shl	bx,1
+	mov	bx,[es:charloc+bx]		;BX holds pointer to character data
+
+;
+; look up which shift table to use, based on bufferbit
+;
+	mov	di,[bufferbit]
+	shl	di,1
+	mov	bp,[shifttabletable+di]	;BP holds pointer to shift table
+
+	mov	di,OFFSET databuffer
+	add	di,[bufferbyte]			;DI holds pointer to buffer
+
+	mov	cx,[bufferbit]
+	add	cx,si					;add twice because pixel == two bits
+	add	cx,si					;new bit position
+	mov	ax,cx
+	and	ax,7
+	mov	[bufferbit],ax			;new bit position
+	mov	ax,cx
+	shr	ax,1
+	shr	ax,1
+	shr	ax,1
+	add	[bufferbyte],ax			;new byte position
+
+	add	si,3
+	shr	si,1
+	shr	si,1					;bytes the character is wide
+	shl	si,1                    ;*2 to look up in shiftdrawtable
+
+	mov	cx,[es:pcharheight]
+	mov	dx,BUFFWIDTH
+	jmp	[ss:shiftdrawtable+si]	;procedure to draw this width
+
+;
+; one byte character
+;
+shift1wide:
+	dec	dx
+EVEN
+@@loop1:
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+
+	loop	@@loop1
+
+	ret
+
+;
+; two byte character
+;
+shift2wide:
+	dec	dx
+	dec	dx
+EVEN
+@@loop2:
+	SHIFTNOXOR
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+
+	loop	@@loop2
+
+	ret
+
+;
+; three byte character
+;
+shift3wide:
+	sub	dx,3
+EVEN
+@@loop3:
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+
+	loop	@@loop3
+
+	ret
+
+
+;
+; four byte character
+;
+shift4wide:
+	sub	dx,4
+EVEN
+@@loop4:
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+
+	loop	@@loop4
+
+	ret
+
+
+;
+; five byte character
+;
+shift5wide:
+	sub	dx,5
+EVEN
+@@loop5:
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+
+	loop	@@loop5
+
+	ret
+
+;
+; six byte character
+;
+shift6wide:
+	sub	dx,6
+EVEN
+@@loop6:
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+
+	loop	@@loop6
+
+	ret
+
+
+
+ENDP
+
+;============================================================================
+
+;==================
+;
+; VW_DrawPropString
+;
+; Draws a C string of characters at px/py and advances px
+;
+;==================
+
+CODESEG
+
+PROC	VW_DrawPropString	string:DWORD
+PUBLIC	VW_DrawPropString
+USES	SI,DI
+
+;
+; proportional spaceing, which clears the buffer ahead of it, so only
+; clear the first collumn
+;
+	mov	al,0
+line	=	0
+REPT	BUFFHEIGHT
+	mov	[BYTE databuffer+BUFFWIDTH*line],al
+line	=	line+1
+ENDM
+
+;
+; shift the characters into the buffer
+;
+@@shiftchars:
+	mov	ax,[px]
+	and	ax,3
+	shl	ax,1			;one pixel == two bits
+	mov	[bufferbit],ax
+	mov	[bufferbyte],0
+
+	mov	ax,[WORD string]
+	mov	[stringptr],ax
+	mov	ax,[WORD string+2]
+	mov	[stringptr+2],ax
+
+@@shiftone:
+	mov	es,[stringptr+2]
+	mov	bx,[stringptr]
+	inc	[stringptr]
+	mov	bx,[es:bx]
+	xor	bh,bh
+	or	bl,bl
+	jz	@@allshifted
+	call	ShiftPropChar
+	jmp	@@shiftone
+
+@@allshifted:
+;
+; calculate position to draw buffer on screen
+;
+	mov	bx,[py]
+	shl	bx,1
+	mov	di,[ylookup+bx]
+	add	di,[bufferofs]
+	add	di,[panadjust]
+
+	mov	ax,[px]
+	shr	ax,1
+	shr	ax,1		;x location in bytes
+	add	di,ax
+	mov	[screenspot],di
+
+;
+; advance px
+;
+	mov	ax,[bufferbyte]
+	shl	ax,1
+	shl	ax,1
+	mov	bx,[bufferbit]
+	shr	bx,1			;two bits == one pixel
+	or	ax,bx
+	add	[px],ax
+
+;
+; draw it
+;
+	mov	ax,[bufferbyte]
+	test	[bufferbit],7
+	jz	@@go
+	inc	ax				;so the partial byte also gets drawn
+@@go:
+	mov	[bufferwidth],ax
+	mov	si,[fontnumber]
+	shl	si,1
+	mov	es,[grsegs+STARTFONT*2+si]
+	mov	ax,[es:pcharheight]
+	mov	[bufferheight],ax
+
+	mov	si,OFFSET databuffer
+	call	VWL_XORBuffer
+
+	ret
+
+ENDP
+
+endif	;numfont
+
+;============================================================================
+;
+; MASKED FONT DRAWING ROUTINES
+;
+;============================================================================
+
+if	numfontm
+
+DATASEG
+
+mshiftdrawtable	dw      0,mshift1wide,mshift2wide,mshift3wide
+
+
+CODESEG
+
+;==================
+;
+; ShiftMPropChar
+;
+; Call with BX = character number (0-255)
+; Draws one character to the buffer at bufferbyte/bufferbit, and adjusts
+; them to the new position
+;
+;==================
+
+PROC	ShiftMPropChar	NEAR
+
+	mov	es,[grsegs+STARTFONTM*2]	;segment of font to use
+
+;
+; find character location, width, and height
+;
+	mov	si,[es:charwidth+bx]
+	and	si,0ffh					;SI hold width in pixels
+	shl	bx,1
+	mov	bx,[es:charloc+bx]		;BX holds pointer to character data
+
+;
+; look up which shift table to use, based on bufferbit
+;
+	mov	di,[bufferbit]
+	shl	di,1
+	mov	bp,[shifttabletable+di]	;BP holds pointer to shift table
+
+	mov	di,OFFSET databuffer
+	add	di,[bufferbyte]			;DI holds pointer to buffer
+
+;
+; advance position by character width
+;
+	mov	cx,[bufferbit]
+	add	cx,si					;new bit position
+	mov	ax,cx
+	and	ax,7
+	mov	[bufferbit],ax			;new bit position
+	mov	ax,cx
+	shr	ax,1
+	shr	ax,1
+	shr	ax,1
+	add	[bufferbyte],ax			;new byte position
+
+	add	si,7
+	shr	si,1
+	shr	si,1
+	shr	si,1					;bytes the character is wide
+	shl	si,1                    ;*2 to look up in shiftdrawtable
+
+	mov	cx,[es:pcharheight]
+	mov	dx,BUFFWIDTH
+	jmp	[ss:mshiftdrawtable+si]	;procedure to draw this width
+
+;
+; one byte character
+;
+mshift1wide:
+	dec	dx
+
+EVEN
+@@loop1m:
+	SHIFTWITHXOR
+	add	di,dx			; next line in buffer
+
+	loop	@@loop1m
+
+	mov	cx,[es:pcharheight]
+
+EVEN
+@@loop1:
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+	loop	@@loop1
+
+	ret
+
+;
+; two byte character
+;
+mshift2wide:
+	dec	dx
+	dec	dx
+EVEN
+@@loop2m:
+	SHIFTWITHXOR
+	SHIFTWITHXOR
+	add	di,dx			; next line in buffer
+
+	loop	@@loop2m
+
+	mov	cx,[es:pcharheight]
+
+EVEN
+@@loop2:
+	SHIFTNOXOR
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+	loop	@@loop2
+
+	ret
+
+;
+; three byte character
+;
+mshift3wide:
+	sub	dx,3
+EVEN
+@@loop3m:
+	SHIFTWITHXOR
+	SHIFTWITHXOR
+	SHIFTWITHXOR
+	add	di,dx			; next line in buffer
+
+	loop	@@loop3m
+
+	mov	cx,[es:pcharheight]
+
+EVEN
+@@loop3:
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+	loop	@@loop3
+
+	ret
+
+
+ENDP
+
+;============================================================================
+
+;==================
+;
+; VW_DrawMPropString
+;
+; Draws a C string of characters at px/py and advances px
+;
+;==================
+
+
+
+PROC	VW_DrawMPropString	string:DWORD
+PUBLIC	VW_DrawMPropString
+USES	SI,DI
+
+;
+; clear out the first byte of the buffer, the rest will automatically be
+; cleared as characters are drawn into it
+;
+	mov	es,[grsegs+STARTFONTM*2]
+	mov	dx,[es:pcharheight]
+	mov	di,OFFSET databuffer
+	mov	ax,ds
+	mov	es,ax
+	mov	bx,BUFFWIDTH-1
+
+	mov	cx,dx
+	mov	al,0ffh
+@@maskfill:
+	stosb				; fill the mask part with $ff
+	add	di,bx
+	loop	@@maskfill
+
+	mov	cx,dx
+	xor	al,al
+@@datafill:
+	stosb				; fill the data part with $0
+	add	di,bx
+	loop	@@datafill
+
+;
+; shift the characters into the buffer
+;
+	mov	ax,[px]
+	and	ax,7
+	mov	[bufferbit],ax
+	mov	[bufferbyte],0
+
+	mov	ax,[WORD string]
+	mov	[stringptr],ax
+	mov	ax,[WORD string+2]
+	mov	[stringptr+2],ax
+
+@@shiftone:
+	mov	es,[stringptr+2]
+	mov	bx,[stringptr]
+	inc	[stringptr]
+	mov	bx,[es:bx]
+	xor	bh,bh
+	or	bl,bl
+	jz	@@allshifted
+	call	ShiftMPropChar
+	jmp	@@shiftone
+
+@@allshifted:
+;
+; calculate position to draw buffer on screen
+;
+	mov	bx,[py]
+	shl	bx,1
+	mov	di,[ylookup+bx]
+	add	di,[bufferofs]
+
+	mov	ax,[px]
+	shr	ax,1
+	shr	ax,1
+	shr	ax,1		;x location in bytes
+	add	di,ax
+	mov	[screenspot],di
+
+;
+; advance px
+;
+	mov	ax,[bufferbyte]
+	shl	ax,1
+	shl	ax,1
+	shl	ax,1
+	or	ax,[bufferbit]
+	add	[px],ax
+
+;
+; draw it
+;
+	mov	ax,[bufferbyte]
+	test	[bufferbit],7
+	jz	@@go
+	inc	ax				;so the partial byte also gets drawn
+@@go:
+	mov	[bufferwidth],ax
+	mov	es,[grsegs+STARTFONTM*2]
+	mov	ax,[es:pcharheight]
+	mov	[bufferheight],ax
+
+	mov	si,OFFSET databuffer
+	call	BufferToScreen		; cut out mask
+								; or in data
+	call	BufferToScreen		; SI is still in the right position in buffer
+
+	ret
+
+ENDP
+
+endif		; if numfontm
+
+endif		; if fonts
diff --git a/16/keen456/KEEN4-6/ID_VW_AE.ASM b/16/keen456/KEEN4-6/ID_VW_AE.ASM
new file mode 100755
index 00000000..37d4e9e2
--- /dev/null
+++ b/16/keen456/KEEN4-6/ID_VW_AE.ASM
@@ -0,0 +1,1824 @@
+; Reconstructed Commander Keen 4-6 Source Code
+; Copyright (C) 2021 K1n9_Duk3
+;
+; This file is primarily based on:
+; Catacomb 3-D Source Code
+; Copyright (C) 1993-2014 Flat Rock Software
+;
+; This program is free software; you can redistribute it and/or modify
+; it under the terms of the GNU General Public License as published by
+; the Free Software Foundation; either version 2 of the License, or
+; (at your option) any later version.
+;
+; This program is distributed in the hope that it will be useful,
+; but WITHOUT ANY WARRANTY; without even the implied warranty of
+; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+; GNU General Public License for more details.
+;
+; You should have received a copy of the GNU General Public License along
+; with this program; if not, write to the Free Software Foundation, Inc.,
+; 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+
+;=================================
+;
+; EGA view manager routines
+;
+;=================================
+
+;============================================================================
+;
+; All EGA drawing routines that write out words need to have alternate forms
+; for starting on even and odd addresses, because writing a word at segment
+; offset 0xffff causes an exception!  To work around this, write a single
+; byte out to make the address even, so it wraps cleanly at the end.
+;
+; All of these routines assume read/write mode 0, and will allways return
+; in that state.
+; The direction flag should be clear
+; readmap/writemask is left in an undefined state
+;
+;============================================================================
+
+
+;============================================================================
+;
+; VW_Plot (int x,y,color)
+;
+;============================================================================
+
+DATASEG
+
+plotpixels	db	128,64,32,16,8,4,2,1
+
+CODESEG
+
+PROC	VW_Plot x:WORD, y:WORD, color:WORD
+PUBLIC	VW_Plot
+USES	SI,DI
+
+	mov	es,[screenseg]
+
+	mov	dx,SC_INDEX
+	mov	ax,SC_MAPMASK+15*256
+	WORDOUT
+
+	mov	dx,GC_INDEX
+	mov	ax,GC_MODE+2*256	;write mode 2
+	WORDOUT
+
+	mov	di,[bufferofs]
+	mov	bx,[y]
+	shl	bx,1
+	add	di,[ylookup+bx]
+	mov	bx,[x]
+	mov	ax,bx
+	shr	ax,1
+	shr	ax,1
+	shr	ax,1
+	add	di,ax				; di = byte on screen
+
+	and	bx,7
+	mov	ah,[plotpixels+bx]
+	mov	al,GC_BITMASK		;mask off other pixels
+	WORDOUT
+
+	mov		bl,[BYTE color]
+	xchg	bl,[es:di]		; load latches and write pixel
+
+	mov	dx,GC_INDEX
+	mov	ah,0ffh				;no bit mask
+	WORDOUT
+	mov	ax,GC_MODE+0*256	;write mode 0
+	WORDOUT
+
+	ret
+
+ENDP
+
+
+;============================================================================
+;
+; VW_Vlin (int yl,yh,x,color)
+;
+;============================================================================
+
+PROC	VW_Vlin yl:WORD, yh:WORD, x:WORD, color:WORD
+PUBLIC	VW_Vlin
+USES	SI,DI
+
+	mov	es,[screenseg]
+
+	mov	dx,SC_INDEX
+	mov	ax,SC_MAPMASK+15*256
+	WORDOUT
+
+	mov	dx,GC_INDEX
+	mov	ax,GC_MODE+2*256	;write mode 2
+	WORDOUT
+
+	mov	di,[bufferofs]
+	mov	bx,[yl]
+	shl	bx,1
+	add	di,[ylookup+bx]
+	mov	bx,[x]
+	mov	ax,bx
+	shr	ax,1
+	shr	ax,1
+	shr	ax,1
+	add	di,ax				; di = byte on screen
+
+	and	bx,7
+	mov	ah,[plotpixels+bx]
+	mov	al,GC_BITMASK		;mask off other pixels
+	WORDOUT
+
+	mov	cx,[yh]
+	sub	cx,[yl]
+	inc	cx					;number of pixels to plot
+
+	mov	bh,[BYTE color]
+	mov	dx,[linewidth]
+
+@@plot:
+	mov		bl,bh
+	xchg	bl,[es:di]		; load latches and write pixel
+	add		di,dx
+
+	loop	@@plot
+
+	mov	dx,GC_INDEX
+	mov	ah,0ffh				;no bit mask
+	WORDOUT
+	mov	ax,GC_MODE+0*256	;write mode 0
+	WORDOUT
+
+	ret
+
+ENDP
+
+
+;============================================================================
+
+
+;===================
+;
+; VW_DrawTile8
+;
+; xcoord in bytes (8 pixels), ycoord in pixels
+; All Tile8s are in one grseg, so an offset is calculated inside it
+;
+;===================
+
+PROC	VW_DrawTile8	xcoord:WORD, ycoord:WORD, tile:WORD
+PUBLIC	VW_DrawTile8
+USES	SI,DI
+
+	mov	es,[screenseg]
+
+	mov	di,[bufferofs]
+	add	di,[xcoord]
+	mov	bx,[ycoord]
+	shl	bx,1
+	add	di,[ylookup+bx]
+	mov	[ss:screendest],di		;screen destination
+
+	mov	bx,[linewidth]
+	dec	bx
+
+	mov	si,[tile]
+	shl	si,1
+	shl	si,1
+	shl	si,1
+	shl	si,1
+	shl	si,1
+
+	mov	ds,[grsegs+STARTTILE8*2] ; segment for all tile8s
+
+	mov	cx,4					;planes to draw
+	mov	ah,0001b				;map mask
+
+	mov	dx,SC_INDEX
+	mov	al,SC_MAPMASK
+
+;
+; start drawing
+;
+
+@@planeloop:
+	WORDOUT
+	shl	ah,1					;shift plane mask over for next plane
+
+	mov	di,[ss:screendest]		;start at same place in all planes
+
+REPT	7
+	movsb
+	add	di,bx
+ENDM
+	movsb
+
+	loop	@@planeloop
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+ENDP
+
+
+;============================================================================
+;
+; VW_MaskBlock
+;
+; Draws a masked block shape to the screen.  bufferofs is NOT accounted for.
+; The mask comes first, then four planes of data.
+;
+;============================================================================
+
+DATASEG
+
+UNWOUNDMASKS	=	10
+
+
+maskroutines	dw	mask0,mask0,mask1E,mask1E,mask2E,mask2O,mask3E,mask3O
+				dw	mask4E,mask4O,mask5E,mask5O,mask6E,mask6O
+				dw	mask7E,mask7O,mask8E,mask8O,mask9E,mask9O
+				dw	mask10E,mask10O
+
+
+routinetouse	dw	?
+
+CODESEG
+
+PROC	VW_MaskBlock	segm:WORD, ofs:WORD, dest:WORD, wide:WORD, height:WORD, planesize:WORD
+PUBLIC	VW_MaskBlock
+USES	SI,DI
+
+	mov	es,[screenseg]
+
+	mov	[BYTE planemask],1
+	mov	[BYTE planenum],0
+
+	mov	di,[wide]
+	mov	dx,[linewidth]
+	sub	dx,[wide]
+	mov	[linedelta],dx			;amount to add after drawing each line
+
+	mov	bx,[planesize]			; si+bx = data location
+
+	cmp	di,UNWOUNDMASKS
+	jbe	@@unwoundroutine
+	mov	[routinetouse],OFFSET generalmask
+	jmp	NEAR @@startloop
+
+;=================
+;
+; use the unwound routines
+;
+;=================
+
+@@unwoundroutine:
+	mov	cx,[dest]
+	shr	cx,1
+	rcl	di,1					;shift a 1 in if destination is odd
+	shl	di,1					;to index into a word width table
+	mov	ax,[maskroutines+di]	;call the right routine
+	mov	[routinetouse],ax
+
+@@startloop:
+	mov	ds,[segm]
+
+@@drawplane:
+	mov	dx,SC_INDEX
+	mov	al,SC_MAPMASK
+	mov	ah,[ss:planemask]
+	WORDOUT
+	mov	dx,GC_INDEX
+	mov	al,GC_READMAP
+	mov	ah,[ss:planenum]
+	WORDOUT
+
+	mov	si,[ofs]				;start back at the top of the mask
+	mov	di,[dest]				;start at same place in all planes
+	mov	cx,[height]				;scan lines to draw
+	mov dx,[ss:linedelta]
+
+	jmp [ss:routinetouse]		;draw one plane
+planereturn:					;routine jmps back here
+
+	add	bx,[ss:planesize]		;start of mask = start of next plane
+
+	inc	[ss:planenum]
+	shl	[ss:planemask],1		;shift plane mask over for next plane
+	cmp	[ss:planemask],10000b	;done all four planes?
+	jne	@@drawplane
+
+mask0:
+	mov	ax,ss
+	mov	ds,ax
+	ret							;width of 0 = no drawing
+
+;==============
+;
+; General purpose masked block drawing.  This could be optimised into
+; four routines to use words, but few play loop sprites should be this big!
+;
+;==============
+
+generalmask:
+	mov	dx,cx
+
+@@lineloopgen:
+	mov	cx,[wide]
+@@byteloop:
+	mov	al,[es:di]
+	and	al,[si]
+	or	al,[bx+si]
+	inc	si
+	stosb
+	loop	@@byteloop
+
+	add	di,[ss:linedelta]
+	dec	dx
+	jnz	@@lineloopgen
+	jmp	planereturn
+
+;=================
+;
+; Horizontally unwound routines to draw certain masked blocks faster
+;
+;=================
+
+MACRO	MASKBYTE
+	lodsb
+	and	al,[es:di]
+	or	al,[bx+si-1]
+	stosb
+ENDM
+
+MACRO	MASKWORD
+	lodsw
+	and	ax,[es:di]
+	or	ax,[bx+si-2]
+	stosw
+ENDM
+
+MACRO	SPRITELOOP	addr
+	add	di,dx
+	loop	addr
+	jmp	planereturn
+ENDM
+
+
+EVEN
+mask1E:
+	MASKBYTE
+	SPRITELOOP	mask1E
+
+EVEN
+mask2E:
+	MASKWORD
+	SPRITELOOP	mask2E
+
+EVEN
+mask2O:
+	MASKBYTE
+	MASKBYTE
+	SPRITELOOP	mask2O
+
+EVEN
+mask3E:
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask3E
+
+EVEN
+mask3O:
+	MASKBYTE
+	MASKWORD
+	SPRITELOOP	mask3O
+
+EVEN
+mask4E:
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask4E
+
+EVEN
+mask4O:
+	MASKBYTE
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask4O
+
+EVEN
+mask5E:
+	MASKWORD
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask5E
+
+EVEN
+mask5O:
+	MASKBYTE
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask5O
+
+EVEN
+mask6E:
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask6E
+
+EVEN
+mask6O:
+	MASKBYTE
+	MASKWORD
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask6O
+
+EVEN
+mask7E:
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask7E
+
+EVEN
+mask7O:
+	MASKBYTE
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask7O
+
+EVEN
+mask8E:
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask8E
+
+EVEN
+mask8O:
+	MASKBYTE
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask8O
+
+EVEN
+mask9E:
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask9E
+
+EVEN
+mask9O:
+	MASKBYTE
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask9O
+
+EVEN
+mask10E:
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	SPRITELOOP	mask10E
+
+EVEN
+mask10O:
+	MASKBYTE
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKWORD
+	MASKBYTE
+	SPRITELOOP	mask10O
+
+
+ENDP
+
+
+;============================================================================
+;
+; VW_InverseMask
+;
+; Draws a masked block shape to the screen.  bufferofs is NOT accounted for.
+; The mask comes first, then four planes of data.
+;
+;============================================================================
+
+PROC	VW_InverseMask	segm:WORD, ofs:WORD, dest:WORD, wide:WORD, height:WORD
+PUBLIC	VW_InverseMask
+USES	SI,DI
+
+	mov	dx,SC_INDEX
+	mov	ax,SC_MAPMASK+15*256
+	WORDOUT
+	mov	dx,GC_INDEX
+	mov	ax,GC_DATAROTATE+16*256		;set function = OR
+	WORDOUT
+
+	mov	es, [screenseg]
+	mov	ax, [wide]
+	mov	dx, [linewidth]
+	sub	dx, ax;
+	mov	ds, [segm]
+	mov	si, [ofs]
+	mov	di, [dest]
+	mov	bx, [height]
+@@yloop:
+	mov	cx, [wide]
+@@xloop:
+	lodsb
+	not	al
+	xchg	al, [es:di]
+	inc	di
+	loop	@@xloop
+	add	di, dx
+	dec	bx
+	jnz	@@yloop
+
+	mov	dx,GC_INDEX
+	mov	ax,GC_DATAROTATE+0*256		;set function = no change
+	WORDOUT
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+ENDP
+
+;============================================================================
+;
+; VW_ScreenToScreen
+;
+; Basic block copy routine.  Copies one block of screen memory to another,
+; using write mode 1 (sets it and returns with write mode 0).  bufferofs is
+; NOT accounted for.
+;
+;============================================================================
+
+PROC	VW_ScreenToScreen	source:WORD, dest:WORD, wide:WORD, height:WORD
+PUBLIC	VW_ScreenToScreen
+USES	SI,DI
+
+	pushf
+	cli
+
+	mov	dx,SC_INDEX
+	mov	ax,SC_MAPMASK+15*256
+	WORDOUT
+	mov	dx,GC_INDEX
+	mov	ax,GC_MODE+1*256
+	WORDOUT
+
+	popf
+
+	mov	bx,[linewidth]
+	sub	bx,[wide]
+
+	mov	ax,[screenseg]
+	mov	es,ax
+	mov	ds,ax
+
+	mov	si,[source]
+	mov	di,[dest]				;start at same place in all planes
+	mov	dx,[height]				;scan lines to draw
+	mov	ax,[wide]
+
+@@lineloop:
+	mov	cx,ax
+	rep	movsb
+	add	si,bx
+	add	di,bx
+
+	dec	dx
+	jnz	@@lineloop
+
+	mov	dx,GC_INDEX
+	mov	ax,GC_MODE+0*256
+	WORDOUT
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+ENDP
+
+
+;============================================================================
+;
+; VW_MemToScreen
+;
+; Basic block drawing routine. Takes a block shape at segment pointer source
+; with four planes of width by height data, and draws it to dest in the
+; virtual screen, based on linewidth.  bufferofs is NOT accounted for.
+; There are four drawing routines to provide the best optimized code while
+; accounting for odd segment wrappings due to the floating screens.
+;
+;============================================================================
+
+DATASEG
+
+memtoscreentable	dw	eventoeven,eventoodd,oddtoeven,oddtoodd
+
+CODESEG
+
+
+PROC	VW_MemToScreen	source:WORD, dest:WORD, wide:WORD, height:WORD
+PUBLIC	VW_MemToScreen
+USES	SI,DI
+
+	mov	es,[screenseg]
+
+	mov	bx,[linewidth]
+	sub	bx,[wide]
+
+	mov	ds,[source]
+
+
+	xor	si,si					;block is segment aligned
+
+	xor	di,di
+	shr	[wide],1				;change wide to words, and see if carry is set
+	rcl	di,1					;1 if wide is odd
+	mov	ax,[dest]
+	shr	ax,1
+	rcl	di,1					;shift a 1 in if destination is odd
+	shl	di,1					;to index into a word width table
+	mov	ax,SC_MAPMASK+0001b*256	;map mask for plane 0
+	jmp	[ss:memtoscreentable+di]	;call the right routine
+
+;==============
+;
+; Copy an even width block to an even video address
+;
+;==============
+
+eventoeven:
+	mov	dx,SC_INDEX
+	WORDOUT
+
+	mov	di,[dest]				;start at same place in all planes
+	mov	dx,[height]				;scan lines to draw
+
+@@lineloopEE:
+	mov	cx,[wide]
+	rep	movsw
+
+	add	di,bx
+
+	dec	dx
+	jnz	@@lineloopEE
+
+	shl	ah,1					;shift plane mask over for next plane
+	cmp	ah,10000b				;done all four planes?
+	jne	eventoeven
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+;==============
+;
+; Copy an odd width block to an even video address
+;
+;==============
+
+oddtoeven:
+	mov	dx,SC_INDEX
+	WORDOUT
+
+	mov	di,[dest]				;start at same place in all planes
+	mov	dx,[height]				;scan lines to draw
+
+@@lineloopOE:
+	mov	cx,[wide]
+	rep	movsw
+	movsb						;copy the last byte
+
+	add	di,bx
+
+	dec	dx
+	jnz	@@lineloopOE
+
+	shl	ah,1					;shift plane mask over for next plane
+	cmp	ah,10000b				;done all four planes?
+	jne	oddtoeven
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+;==============
+;
+; Copy an even width block to an odd video address
+;
+;==============
+
+eventoodd:
+	dec	[wide]					;one word has to be handled seperately
+EOplaneloop:
+	mov	dx,SC_INDEX
+	WORDOUT
+
+	mov	di,[dest]				;start at same place in all planes
+	mov	dx,[height]				;scan lines to draw
+
+@@lineloopEO:
+	movsb
+	mov	cx,[wide]
+	rep	movsw
+	movsb
+
+	add	di,bx
+
+	dec	dx
+	jnz	@@lineloopEO
+
+	shl	ah,1					;shift plane mask over for next plane
+	cmp	ah,10000b				;done all four planes?
+	jne	EOplaneloop
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+;==============
+;
+; Copy an odd width block to an odd video address
+;
+;==============
+
+oddtoodd:
+	mov	dx,SC_INDEX
+	WORDOUT
+
+	mov	di,[dest]				;start at same place in all planes
+	mov	dx,[height]				;scan lines to draw
+
+@@lineloopOO:
+	movsb
+	mov	cx,[wide]
+	rep	movsw
+
+	add	di,bx
+
+	dec	dx
+	jnz	@@lineloopOO
+
+	shl	ah,1					;shift plane mask over for next plane
+	cmp	ah,10000b				;done all four planes?
+	jne	oddtoodd
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+
+ENDP
+
+;===========================================================================
+;
+; VW_ScreenToMem
+;
+; Copies a block of video memory to main memory, in order from planes 0-3.
+; This could be optimized along the lines of VW_MemToScreen to take advantage
+; of word copies, but this is an infrequently called routine.
+;
+;===========================================================================
+
+PROC	VW_ScreenToMem	source:WORD, dest:WORD, wide:WORD, height:WORD
+PUBLIC	VW_ScreenToMem
+USES	SI,DI
+
+	mov	es,[dest]
+
+	mov	bx,[linewidth]
+	sub	bx,[wide]
+
+	mov	ds,[screenseg]
+
+	mov	ax,GC_READMAP			;read map for plane 0
+
+	xor	di,di
+
+@@planeloop:
+	mov	dx,GC_INDEX
+	WORDOUT
+
+	mov	si,[source]				;start at same place in all planes
+	mov	dx,[height]				;scan lines to draw
+
+@@lineloop:
+	mov	cx,[wide]
+	rep	movsb
+
+	add	si,bx
+
+	dec	dx
+	jnz	@@lineloop
+
+	inc	ah
+	cmp	ah,4					;done all four planes?
+	jne	@@planeloop
+
+	mov	ax,ss
+	mov	ds,ax					;restore turbo's data segment
+
+	ret
+
+ENDP
+
+
+;============================================================================
+;
+; VWL_UpdateScreenBlocks
+;
+; Scans through the update matrix and copies any areas that have changed
+; to the visable screen, then zeros the update array
+;
+;============================================================================
+
+
+
+; AX	0/1 for scasb, temp for segment register transfers
+; BX    width for block copies
+; CX	REP counter
+; DX	line width deltas
+; SI	source for copies
+; DI	scas dest / movsb dest
+; BP	pointer to end of bufferblocks
+
+PROC	VWL_UpdateScreenBlocks
+PUBLIC	VWL_UpdateScreenBlocks
+USES	SI,DI,BP
+
+	jmp	SHORT @@realstart
+@@done:
+;
+; all tiles have been scanned
+;
+	mov	dx,GC_INDEX				; restore write mode 0
+	mov	ax,GC_MODE+0*256
+	WORDOUT
+
+	xor	ax,ax					; clear out the update matrix
+	mov	cx,UPDATEWIDE*UPDATEHIGH/2
+
+	mov	di,[updateptr]
+	rep	stosw
+
+	ret
+
+@@realstart:
+	mov	dx,SC_INDEX
+	mov	ax,SC_MAPMASK+15*256
+	WORDOUT
+	mov	dx,GC_INDEX
+	mov	ax,GC_MODE+1*256
+	WORDOUT
+
+	mov	di,[updateptr]			; start of floating update screen
+	mov	bp,di
+	add	bp,UPDATEWIDE*UPDATEHIGH+1 ; when di = bp, all tiles have been scanned
+
+	push	di
+	mov	cx,-1					; definately scan the entire thing
+
+;
+; scan for a 1 in the update list, meaning a tile needs to be copied
+; from the master screen to the current screen
+;
+@@findtile:
+	pop	di						; place to continue scaning from
+	mov	ax,ss
+	mov	es,ax					; search in the data segment
+	mov	ds,ax
+	mov al,1
+	repne	scasb
+	cmp	di,bp
+	jae	@@done
+
+	cmp	[BYTE di],al
+	jne	@@singletile
+	jmp	@@tileblock
+
+;============
+;
+; copy a single tile
+;
+;============
+@@singletile:
+	inc	di						; we know the next tile is nothing
+	push	di					; save off the spot being scanned
+	sub	di,[updateptr]
+	shl	di,1
+	mov	di,[blockstarts-4+di]	; start of tile location on screen
+	mov	si,di
+	add	si,[bufferofs]
+	add	di,[displayofs]
+
+	mov	dx,[linewidth]
+	sub	dx,2
+	mov	ax,[screenseg]
+	mov	ds,ax
+	mov	es,ax
+
+REPT	15
+	movsb
+	movsb
+	add	si,dx
+	add	di,dx
+ENDM
+	movsb
+	movsb
+
+	jmp	@@findtile
+
+;============
+;
+; more than one tile in a row needs to be updated, so do it as a group
+;
+;============
+EVEN
+@@tileblock:
+	mov	dx,di					; hold starting position + 1 in dx
+	inc	di						; we know the next tile also gets updated
+	repe	scasb				; see how many more in a row
+	push	di					; save off the spot being scanned
+
+	mov	bx,di
+	sub	bx,dx					; number of tiles in a row
+	shl	bx,1					; number of bytes / row
+
+	mov	di,dx					; lookup position of start tile
+	sub	di,[updateptr]
+	shl	di,1
+	mov	di,[blockstarts-2+di]	; start of tile location
+	mov	si,di
+	add	si,[bufferofs]
+	add	di,[displayofs]
+
+	mov	dx,[linewidth]
+	sub	dx,bx					; offset to next line on screen
+
+	mov	ax,[screenseg]
+	mov	ds,ax
+	mov	es,ax
+
+REPT	15
+	mov	cx,bx
+	rep	movsb
+	add	si,dx
+	add	di,dx
+ENDM
+	mov	cx,bx
+	rep	movsb
+
+	dec	cx						; was 0 from last rep movsb, now $ffff for scasb
+	jmp	@@findtile
+
+ENDP
+
+
+;===========================================================================
+;
+;                    MISC EGA ROUTINES
+;
+;===========================================================================
+
+;=================
+;
+; SyncVBL
+;
+;=================
+
+DATASEG
+
+EXTRN	TimeCount			:DWORD
+EXTRN	jerk			:WORD
+EXTRN	nopan				:WORD
+
+CODESEG
+
+PROC SyncVBL
+	mov	dx,STATUS_REGISTER_1
+	mov	bx,[WORD TimeCount]
+	add	bx,3
+@@waitloop:
+	sti
+	jmp	$+2
+	cli
+	cmp	[WORD TimeCount],bx
+	je	@@done
+@@waitnovert:
+	in	al,dx
+	test	al,1
+	jnz	@@waitnovert
+@@waitvert:
+	in	al,dx
+	test	al,1
+	jz	@@waitvert
+
+REPT 5
+	in	al,dx
+	test	al,8
+	jnz	@@waitloop
+	test	al,1
+	jz	@@waitloop
+ENDM
+
+	test	[jerk],1
+	jz	@@done
+
+REPT 5
+	in	al,dx
+	test	al,8
+	jnz	@@waitloop
+	test	al,1
+	jz	@@waitloop
+ENDM
+
+@@done:
+	ret
+ENDP
+
+
+;==============
+;
+; VW_SetScreen
+;
+;==============
+
+PROC	VW_SetScreen  crtc:WORD, pel:WORD
+PUBLIC	VW_SetScreen
+
+	call	SyncVBL
+;
+; set CRTC start
+;
+; for some reason, my XT's EGA card doesn't like word outs to the CRTC
+; index...
+;
+	mov	cx,[crtc]
+	mov	dx,CRTC_INDEX
+	mov	al,0ch		;start address high register
+	out	dx,al
+	inc	dx
+	mov	al,ch
+	out	dx,al
+	dec	dx
+	mov	al,0dh		;start address low register
+	out	dx,al
+	mov	al,cl
+	inc	dx
+	out	dx,al
+
+	test	[nopan],1
+	jnz	@@done
+;
+; set horizontal panning
+;
+
+	mov	dx,ATR_INDEX
+	mov	al,ATR_PELPAN or 20h
+	out	dx,al
+	jmp	$+2
+	mov	al,[BYTE pel]		;pel pan value
+	out	dx,al
+
+@@done:
+	sti
+
+	ret
+
+ENDP
+
+
+if NUMFONT+NUMFONTM
+
+;===========================================================================
+;
+; GENERAL FONT DRAWING ROUTINES
+;
+;===========================================================================
+
+DATASEG
+
+px	dw	?					; proportional character drawing coordinates
+py	dw	?
+pdrawmode	db	11000b		; 8 = OR, 24 = XOR, put in GC_DATAROTATE
+fontcolor	db	15		;0-15 mapmask value
+
+PUBLIC	px,py,pdrawmode,fontcolor
+
+;
+; offsets in font structure
+;
+pcharheight	=	0		;lines high
+charloc		=	2		;pointers to every character
+charwidth	=	514		;every character's width in pixels
+
+
+propchar	dw	?			; the character number to shift
+stringptr	dw	?,?
+
+
+BUFFWIDTH	=	50
+BUFFHEIGHT	=   32			; must be twice as high as font for masked fonts
+
+databuffer	db	BUFFWIDTH*BUFFHEIGHT dup (?)
+
+bufferwidth	dw	?						; bytes with valid info / line
+bufferheight dw	?						; number of lines currently used
+
+bufferbyte	dw	?
+bufferbit	dw	?
+
+screenspot	dw	?						; where the buffer is going
+
+bufferextra	dw	?						; add at end of a line copy
+screenextra	dw	?
+
+PUBLIC	bufferwidth,bufferheight,screenspot
+
+CODESEG
+
+;======================
+;
+; Macros to table shift a byte of font
+;
+;======================
+
+MACRO	SHIFTNOXOR
+	mov	al,[es:bx]		; source
+	xor	ah,ah
+	shl	ax,1
+	mov	si,ax
+	mov	ax,[bp+si]		; table shift into two bytes
+	or	[di],al			; or with first byte
+	inc	di
+	mov	[di],ah			; replace next byte
+	inc	bx				; next source byte
+ENDM
+
+MACRO	SHIFTWITHXOR
+	mov	al,[es:bx]		; source
+	xor	ah,ah
+	shl	ax,1
+	mov	si,ax
+	mov	ax,[bp+si]		; table shift into two bytes
+	not	ax
+	and	[di],al			; and with first byte
+	inc	di
+	mov	[di],ah			; replace next byte
+	inc	bx				; next source byte
+ENDM
+
+
+;=======================
+;
+; BufferToScreen
+;
+; Pass buffer start in SI (somewhere in databuffer)
+; Draws the buffer to the EGA screen in the current write mode
+;
+;========================
+
+PROC	BufferToScreen	NEAR
+
+	mov	es,[screenseg]
+	mov	di,[screenspot]
+
+	mov	bx,[bufferwidth]		;calculate offsets for end of each line
+	or	bx,bx
+	jnz	@@isthere
+	ret							;nothing to draw
+
+@@isthere:
+	mov	ax,[linewidth]
+	sub	ax,bx
+	mov	[screenextra],ax
+	mov	ax,BUFFWIDTH
+	sub	ax,bx
+	mov	[bufferextra],ax
+
+	mov	bx,[bufferheight]		;lines to copy
+@@lineloop:
+	mov	cx,[bufferwidth]		;bytes to copy
+@@byteloop:
+	lodsb						;get a byte from the buffer
+	xchg	[es:di],al			;load latches and store back to screen
+	inc	di
+
+	loop	@@byteloop
+
+	add	si,[bufferextra]
+	add	di,[screenextra]
+
+	dec	bx
+	jnz	@@lineloop
+
+	ret
+ENDP
+
+
+;============================================================================
+;
+; NON MASKED FONT DRAWING ROUTINES
+;
+;============================================================================
+
+if numfont
+
+DATASEG
+
+shiftdrawtable	dw      0,shift1wide,shift2wide,shift3wide,shift4wide
+				dw		shift5wide
+
+CODESEG
+
+;==================
+;
+; ShiftPropChar
+;
+; Call with BX = character number (0-255)
+; Draws one character to the buffer at bufferbyte/bufferbit, and adjusts
+; them to the new position
+;
+;==================
+
+PROC	ShiftPropChar	NEAR
+
+	mov	si,[fontnumber]
+	shl	si,1
+	mov	es,[grsegs+STARTFONT*2+si]	;segment of font to use
+
+;
+; find character location, width, and height
+;
+	mov	si,[es:charwidth+bx]
+	and	si,0ffh					;SI hold width in pixels
+	shl	bx,1
+	mov	bx,[es:charloc+bx]		;BX holds pointer to character data
+
+;
+; look up which shift table to use, based on bufferbit
+;
+	mov	di,[bufferbit]
+	shl	di,1
+	mov	bp,[shifttabletable+di]	;BP holds pointer to shift table
+
+	mov	di,OFFSET databuffer
+	add	di,[bufferbyte]			;DI holds pointer to buffer
+
+;
+; advance position by character width
+;
+	mov	cx,[bufferbit]
+	add	cx,si					;new bit position
+	mov	ax,cx
+	and	ax,7
+	mov	[bufferbit],ax			;new bit position
+	mov	ax,cx
+	shr	ax,1
+	shr	ax,1
+	shr	ax,1
+	add	[bufferbyte],ax			;new byte position
+
+	add	si,7
+	shr	si,1
+	shr	si,1
+	shr	si,1					;bytes the character is wide
+	shl	si,1                    ;*2 to look up in shiftdrawtable
+
+	mov	cx,[es:pcharheight]
+	mov	dx,BUFFWIDTH
+	jmp	[ss:shiftdrawtable+si]	;procedure to draw this width
+
+;
+; one byte character
+;
+shift1wide:
+	dec	dx
+EVEN
+@@loop1:
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+	loop	@@loop1
+	ret
+
+;
+; two byte character
+;
+shift2wide:
+	dec	dx
+	dec	dx
+EVEN
+@@loop2:
+	SHIFTNOXOR
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+	loop	@@loop2
+	ret
+
+;
+; three byte character
+;
+shift3wide:
+	sub	dx,3
+EVEN
+@@loop3:
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+	loop	@@loop3
+	ret
+
+;
+; four byte character
+;
+shift4wide:
+	sub	dx,4
+EVEN
+@@loop4:
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+	loop	@@loop4
+	ret
+
+;
+; five byte character
+;
+shift5wide:
+	sub	dx,5
+EVEN
+@@loop5:
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+	loop	@@loop5
+	ret
+
+
+
+ENDP
+
+;============================================================================
+
+;==================
+;
+; VW_DrawPropString
+;
+; Draws a C string of characters at px/py and advances px
+;
+; Assumes write mode 0
+;
+;==================
+
+CODESEG
+
+PROC	VW_DrawPropString	string:DWORD
+PUBLIC	VW_DrawPropString
+USES	SI,DI
+
+;
+; proportional spaceing, which clears the buffer ahead of it, so only
+; clear the first collumn
+;
+	mov	al,0
+line	=	0
+REPT	BUFFHEIGHT
+	mov	[BYTE databuffer+BUFFWIDTH*line],al
+line	=	line+1
+ENDM
+
+;
+; shift the characters into the buffer
+;
+@@shiftchars:
+	mov	ax,[px]
+	and	ax,7
+	mov	[bufferbit],ax
+	mov	[bufferbyte],0
+
+	mov	ax,[WORD string]
+	mov	[stringptr],ax
+	mov	ax,[WORD string+2]
+	mov	[stringptr+2],ax
+
+@@shiftone:
+	mov	es,[stringptr+2]
+	mov	bx,[stringptr]
+	inc	[stringptr]
+	mov	bx,[es:bx]
+	xor	bh,bh
+	or	bl,bl
+	jz	@@allshifted
+	call	ShiftPropChar
+	jmp	@@shiftone
+
+@@allshifted:
+;
+; calculate position to draw buffer on screen
+;
+	mov	bx,[py]
+	shl	bx,1
+	mov	di,[ylookup+bx]
+	add	di,[bufferofs]
+	add	di,[panadjust]
+
+	mov	ax,[px]
+	shr	ax,1
+	shr	ax,1
+	shr	ax,1		;x location in bytes
+	add	di,ax
+	mov	[screenspot],di
+
+;
+; advance px
+;
+	mov	ax,[bufferbyte]
+	shl	ax,1
+	shl	ax,1
+	shl	ax,1
+	or	ax,[bufferbit]
+	add	[px],ax
+
+;
+; draw it
+;
+
+; set xor/or mode
+	mov	dx,GC_INDEX
+	mov	al,GC_DATAROTATE
+	mov	ah,[pdrawmode]
+	WORDOUT
+
+; set mapmask to color
+	mov	dx,SC_INDEX
+	mov	al,SC_MAPMASK
+	mov	ah,[fontcolor]
+	WORDOUT
+
+	mov	ax,[bufferbyte]
+	test	[bufferbit],7
+	jz	@@go
+	inc	ax				;so the partial byte also gets drawn
+@@go:
+	mov	[bufferwidth],ax
+	mov	si,[fontnumber]
+	shl	si,1
+	mov	es,[grsegs+STARTFONT*2+si]
+	mov	ax,[es:pcharheight]
+	mov	[bufferheight],ax
+
+	mov	si,OFFSET databuffer
+	call	BufferToScreen
+
+; set copy mode
+	mov	dx,GC_INDEX
+	mov	ax,GC_DATAROTATE
+	WORDOUT
+
+; set mapmask to all
+	mov	dx,SC_INDEX
+	mov	ax,SC_MAPMASK + 15*256
+	WORDOUT
+
+
+	ret
+
+ENDP
+
+endif	;numfont
+
+;============================================================================
+;
+; MASKED FONT DRAWING ROUTINES
+;
+;============================================================================
+
+if	numfontm
+
+DATASEG
+
+mshiftdrawtable	dw      0,mshift1wide,mshift2wide,mshift3wide
+
+
+CODESEG
+
+;==================
+;
+; ShiftMPropChar
+;
+; Call with BX = character number (0-255)
+; Draws one character to the buffer at bufferbyte/bufferbit, and adjusts
+; them to the new position
+;
+;==================
+
+PROC	ShiftMPropChar	NEAR
+
+	mov	si,[fontnumber]
+	shl	si,1
+	mov	es,[grsegs+STARTFONTM*2+si]	;segment of font to use
+
+;
+; find character location, width, and height
+;
+	mov	si,[es:charwidth+bx]
+	and	si,0ffh					;SI hold width in pixels
+	shl	bx,1
+	mov	bx,[es:charloc+bx]		;BX holds pointer to character data
+
+;
+; look up which shift table to use, based on bufferbit
+;
+	mov	di,[bufferbit]
+	shl	di,1
+	mov	bp,[shifttabletable+di]	;BP holds pointer to shift table
+
+	mov	di,OFFSET databuffer
+	add	di,[bufferbyte]			;DI holds pointer to buffer
+
+	mov	cx,[bufferbit]
+	add	cx,si					;new bit position
+	mov	ax,cx
+	and	ax,7
+	mov	[bufferbit],ax			;new bit position
+	mov	ax,cx
+	shr	ax,1
+	shr	ax,1
+	shr	ax,1
+	add	[bufferbyte],ax			;new byte position
+
+	add	si,7
+	shr	si,1
+	shr	si,1
+	shr	si,1					;bytes the character is wide
+	shl	si,1                    ;*2 to look up in shiftdrawtable
+
+	mov	cx,[es:pcharheight]
+	mov	dx,BUFFWIDTH
+	jmp	[ss:mshiftdrawtable+si]	;procedure to draw this width
+
+;
+; one byte character
+;
+mshift1wide:
+	dec	dx
+
+EVEN
+@@loop1m:
+	SHIFTWITHXOR
+	add	di,dx			; next line in buffer
+
+	loop	@@loop1m
+
+	mov	cx,[es:pcharheight]
+
+EVEN
+@@loop1:
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+	loop	@@loop1
+
+	ret
+
+;
+; two byte character
+;
+mshift2wide:
+	dec	dx
+	dec	dx
+EVEN
+@@loop2m:
+	SHIFTWITHXOR
+	SHIFTWITHXOR
+	add	di,dx			; next line in buffer
+
+	loop	@@loop2m
+
+	mov	cx,[es:pcharheight]
+
+EVEN
+@@loop2:
+	SHIFTNOXOR
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+	loop	@@loop2
+
+	ret
+
+;
+; three byte character
+;
+mshift3wide:
+	sub	dx,3
+EVEN
+@@loop3m:
+	SHIFTWITHXOR
+	SHIFTWITHXOR
+	SHIFTWITHXOR
+	add	di,dx			; next line in buffer
+
+	loop	@@loop3m
+
+	mov	cx,[es:pcharheight]
+
+EVEN
+@@loop3:
+	SHIFTNOXOR
+	SHIFTNOXOR
+	SHIFTNOXOR
+	add	di,dx			; next line in buffer
+	loop	@@loop3
+
+	ret
+
+
+ENDP
+
+;============================================================================
+
+;==================
+;
+; VW_DrawMPropString
+;
+; Draws a C string of characters at px/py and advances px
+;
+; Assumes write mode 0
+;
+;==================
+
+
+
+PROC	VW_DrawMPropString	string:DWORD
+PUBLIC	VW_DrawMPropString
+USES	SI,DI
+
+;
+; clear out the first byte of the buffer, the rest will automatically be
+; cleared as characters are drawn into it
+;
+	mov	si,[fontnumber]
+	shl	si,1
+	mov	es,[grsegs+STARTFONTM*2+si]
+	mov	dx,[es:pcharheight]
+	mov	di,OFFSET databuffer
+	mov	ax,ds
+	mov	es,ax
+	mov	bx,BUFFWIDTH-1
+
+	mov	cx,dx
+	mov	al,0ffh
+@@maskfill:
+	stosb				; fill the mask part with $ff
+	add	di,bx
+	loop	@@maskfill
+
+	mov	cx,dx
+	xor	al,al
+@@datafill:
+	stosb				; fill the data part with $0
+	add	di,bx
+	loop	@@datafill
+
+;
+; shift the characters into the buffer
+;
+	mov	ax,[px]
+	and	ax,7
+	mov	[bufferbit],ax
+	mov	[bufferbyte],0
+
+	mov	ax,[WORD string]
+	mov	[stringptr],ax
+	mov	ax,[WORD string+2]
+	mov	[stringptr+2],ax
+
+@@shiftone:
+	mov	es,[stringptr+2]
+	mov	bx,[stringptr]
+	inc	[stringptr]
+	mov	bx,[es:bx]
+	xor	bh,bh
+	or	bl,bl
+	jz	@@allshifted
+	call	ShiftMPropChar
+	jmp	@@shiftone
+
+@@allshifted:
+;
+; calculate position to draw buffer on screen
+;
+	mov	bx,[py]
+	shl	bx,1
+	mov	di,[ylookup+bx]
+	add	di,[bufferofs]
+	add	di,[panadjust]
+
+	mov	ax,[px]
+	shr	ax,1
+	shr	ax,1
+	shr	ax,1		;x location in bytes
+	add	di,ax
+	mov	[screenspot],di
+
+;
+; advance px
+;
+	mov	ax,[bufferbyte]
+	shl	ax,1
+	shl	ax,1
+	shl	ax,1
+	or	ax,[bufferbit]
+	add	[px],ax
+
+;
+; draw it
+;
+	mov	ax,[bufferbyte]
+	test	[bufferbit],7
+	jz	@@go
+	inc	ax				;so the partial byte also gets drawn
+@@go:
+	mov	[bufferwidth],ax
+	mov	es,[grsegs+STARTFONTM*2]
+	mov	ax,[es:pcharheight]
+	mov	[bufferheight],ax
+
+; set AND mode to punch out the mask
+	mov	dx,GC_INDEX
+	mov	ax,GC_DATAROTATE + 8*256
+	WORDOUT
+
+; set mapmask to all
+	mov	dx,SC_INDEX
+	mov	ax,SC_MAPMASK + 15*256
+	WORDOUT
+
+	mov	si,OFFSET databuffer
+	call	BufferToScreen
+
+; set OR mode to fill in the color
+	mov	dx,GC_INDEX
+	mov	ax,GC_DATAROTATE + 16*256
+	WORDOUT
+
+; set mapmask to color
+	mov	dx,SC_INDEX
+	mov	al,SC_MAPMASK
+	mov	ah,[fontcolor]
+	WORDOUT
+
+	call	BufferToScreen		; SI is still in the right position in buffer
+
+; set copy mode
+	mov	dx,GC_INDEX
+	mov	ax,GC_DATAROTATE
+	WORDOUT
+
+; set mapmask to all
+	mov	dx,SC_INDEX
+	mov	ax,SC_MAPMASK + 15*256
+	WORDOUT
+
+
+	ret
+
+ENDP
+
+endif		; if numfontm
+
+endif		; if fonts
diff --git a/16/keen456/KEEN4-6/KEEN4/AUDIOCK4.H b/16/keen456/KEEN4-6/KEEN4/AUDIOCK4.H
new file mode 100755
index 00000000..835b83e0
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN4/AUDIOCK4.H
@@ -0,0 +1,125 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+#ifndef __AUDIO_H__
+#define __AUDIO_H__
+
+//#include "VERSION.H"
+
+/////////////////////////////////////////////////
+//
+// MUSE Header for .CK4
+//
+/////////////////////////////////////////////////
+
+#define NUMSOUNDS     LASTSOUND
+#define NUMSNDCHUNKS  ((3*LASTSOUND)+LASTMUSIC)
+
+//
+// Sound names & indexes
+//
+typedef enum {
+	SND_WORLDWALK1,
+	SND_WORLDWALK2,
+	SND_JUMP,
+	SND_LAND,
+	SND_KEENFIRE,
+	SND_WORMOUTHATTACK,
+	SND_6,
+	SND_POGOBOUNCE,
+	SND_GETPOINTS,
+	SND_GETAMMO,
+	SND_GETWATER,
+	SND_11,
+	SND_ENTERLEVEL,
+	SND_LEVELDONE,
+	SND_NOWAY,
+	SND_HELMETHIT,
+	SND_BOUNCE2,
+	SND_EXTRAKEEN,
+	SND_OPENDOOR,
+	SND_GETKEY,
+	SND_PLUMMET,
+	SND_USESWITCH,
+	SND_SQUISH,
+	SND_KEENDEAD,
+	SND_24,
+	SND_SHOTEXPLODE,
+	SND_SWIM1,
+	SND_SWIM2,
+	SND_BOUNCE1,
+	SND_EATBONUS,
+	SND_TREASUREEATERVANISH,
+	SND_LINDSEY,
+	SND_LICKATTACK,
+	SND_BERKELOIDATTACK,
+	SND_SHOWSTATUS,
+	SND_HIDESTATUS,
+	SND_BLUB,
+	SND_MINEEXPLODE,
+	SND_SPRITEFIRE,
+	SND_THUNDER,
+	SND_FIREBALLLAND,
+	SND_SHOOTDART,
+	SND_BURP,
+	SND_FLAGSPIN,
+	SND_FLAGLAND,
+	SND_MAKEFOOT,
+	SND_SLUGPOO,
+	KEENPADDLESND,
+	BALLBOUNCESND,
+	COMPPADDLESND,
+	COMPSCOREDSND,
+	KEENSCOREDSND,
+	LASTSOUND
+} soundnames;
+
+#if LASTSOUND != 52
+#error bad sound enum!
+#endif
+
+#define NOWAYSND SND_NOWAY
+
+//
+// Base offsets
+//
+#define STARTPCSOUNDS     0
+#define STARTADLIBSOUNDS  (STARTPCSOUNDS+NUMSOUNDS)
+#define STARTDIGISOUNDS   (STARTADLIBSOUNDS+NUMSOUNDS)
+#define STARTMUSIC        (STARTDIGISOUNDS+NUMSOUNDS)
+
+//
+// Music names & indexes
+//
+typedef enum {
+	SHADOWS_MUS,
+	VEGGIES_MUS,
+	TOOHOT_MUS,
+	OASIS_MUS,
+	KICKPANT_MUS,
+	WONDER_MUS,
+	LASTMUSIC
+} musicnames;
+
+/////////////////////////////////////////////////
+//
+// Thanks for playing with MUSE!
+//
+/////////////////////////////////////////////////
+
+#endif
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/KEEN4/GFXE_CK4.EQU b/16/keen456/KEEN4-6/KEEN4/GFXE_CK4.EQU
new file mode 100755
index 00000000..10a0c2ae
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN4/GFXE_CK4.EQU
@@ -0,0 +1,55 @@
+;=====================================
+;
+; Graphics .EQU file for .CK4
+; not IGRAB-ed :)
+;
+;=====================================
+
+;INCLUDE "VERSION.EQU"
+
+;
+; Amount of each data item
+;
+NUMFONT     =	3
+NUMFONTM    =	0
+NUMPICM     =	3
+NUMTILE8    =	108
+NUMTILE8M   =	36
+NUMTILE32   =	0
+NUMTILE32M  =	0
+
+;
+; Amount of each item in episode 4
+;
+NUMPICS     =	115
+NUMSPRITES  =	397
+NUMTILE16   =	1296
+NUMTILE16M  =	2916
+NUMEXTERN   =	16
+
+
+;
+; File offsets for data items
+;
+STRUCTPIC       =	0
+STRUCTPICM      =	1
+STRUCTSPRITE    =	2
+
+STARTFONT       =	3
+STARTFONTM      =	(STARTFONT+NUMFONT)
+STARTPICS       =	(STARTFONTM+NUMFONTM)
+STARTPICM       =	(STARTPICS+NUMPICS)
+STARTSPRITES    =	(STARTPICM+NUMPICM)
+STARTTILE8      =	(STARTSPRITES+NUMSPRITES)
+STARTTILE8M     =	(STARTTILE8+1)
+STARTTILE16     =	(STARTTILE8M+1)
+STARTTILE16M    =	(STARTTILE16+NUMTILE16)
+STARTTILE32     =	(STARTTILE16M+NUMTILE16M)
+STARTTILE32M    =	(STARTTILE32+NUMTILE32)
+STARTEXTERN     =	(STARTTILE32M+NUMTILE32M)
+
+NUMCHUNKS       =	(STARTEXTERN+NUMEXTERN)
+
+;
+; Thank you for using IGRAB!
+;
diff --git a/16/keen456/KEEN4-6/KEEN4/GFXE_CK4.H b/16/keen456/KEEN4-6/KEEN4/GFXE_CK4.H
new file mode 100755
index 00000000..f1d92bd0
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN4/GFXE_CK4.H
@@ -0,0 +1,765 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+#ifndef __GFX_H__
+#define __GFX_H__
+
+//#include "VERSION.H"
+
+//////////////////////////////////////
+//
+// Graphics .H file for .CK4
+// not IGRAB-ed :)
+//
+//////////////////////////////////////
+
+//
+// Lump creation macros
+//
+
+#define START_LUMP(actualname, dummyname) actualname, dummyname=actualname-1,
+#define END_LUMP(actualname, dummyname) dummyname, actualname=dummyname-1,
+
+//
+// Amount of each data item
+//
+
+//common numbers:
+#define NUMCHUNKS    NUMGRCHUNKS
+#define NUMFONT      3
+#define NUMFONTM     0
+#define NUMPICM      3
+#define NUMTILE8     108	// BUG: only 104 tiles exist in EGAGRAPH!
+#define NUMTILE8M    36		// BUG: only 20 tiles exist in EGAGRAPH!
+#define NUMTILE32    0
+#define NUMTILE32M   0
+
+//episode-specific numbers:
+#define NUMPICS      115
+#define NUMSPRITES   397
+#define NUMTILE16    1296
+#define NUMTILE16M   2916
+#define NUMEXTERNS   16
+
+//
+// File offsets for data items
+//
+#define STRUCTPIC    0
+#define STRUCTPICM   1
+#define STRUCTSPRITE 2
+
+#define STARTFONT    3
+#define STARTFONTM   (STARTFONT+NUMFONT)
+#define STARTPICS    (STARTFONTM+NUMFONTM)
+#define STARTPICM    (STARTPICS+NUMPICS)
+#define STARTSPRITES (STARTPICM+NUMPICM)
+#define STARTTILE8   (STARTSPRITES+NUMSPRITES)
+#define STARTTILE8M  (STARTTILE8+1)
+#define STARTTILE16  (STARTTILE8M+1)
+#define STARTTILE16M (STARTTILE16+NUMTILE16)
+#define STARTTILE32  (STARTTILE16M+NUMTILE16M)
+#define STARTTILE32M (STARTTILE32+NUMTILE32)
+#define STARTEXTERNS (STARTTILE32M+NUMTILE32M)
+
+typedef enum {
+	LASTFONT=STARTPICS-1,
+
+	//
+	// PICS
+	//
+
+	H_HELPPIC,                   // 6
+	H_LARROWPIC,                 // 7
+	H_RARROWPIC,                 // 8
+	H_ESCPIC,                    // 9
+	H_ENTERPIC,                  // 10
+	DUMMYPIC,                    // 11
+	H_STORY1PIC,                 // 12
+	H_STORY2PIC,                 // 13
+	H_STORY3PIC,                 // 14
+	H_STORY4PIC,                 // 15
+	STORY5PIC,                   // 16
+	STORY6PIC,                   // 17
+	STORY7PIC,                   // 18
+	STORY8PIC,                   // 19
+	ITEM1PIC,                    // 20
+	ITEM2PIC,                    // 21
+	ITEM3PIC,                    // 22
+	ITEM4PIC,                    // 23
+	ITEM5PIC,                    // 24
+	ITEM6PIC,                    // 25
+	ITEM7PIC,                    // 26
+	ITEM8PIC,                    // 27
+	ITEM9PIC,                    // 28
+	ARACHNUTPIC,                 // 29
+	BERKELOISPIC,                // 30
+	BOUNDERPIC,                  // 31
+	COUNCILMEMBERPIC,            // 32
+	DOPEFISHPIC,                 // 33
+	INCHWORMPIC,                 // 34
+	LICKPIC,                     // 35
+	MADMUSHROOMPIC,              // 36
+	POISONSLIGPIC,               // 37
+	PRINCESSLINDSEYPIC,          // 38
+	SCHOOLFISHPIC,               // 39
+	SKYPESTPIC,                  // 40
+	SPRITEPIC,                   // 41
+	WORMOUTHPIC,                 // 42
+	ENDOFTEXTPIC,                // 43
+	H_MCPIC,                     // 44
+	H_HANDPIC,                   // 45
+	H_VISAPIC,                   // 46
+	H_FLASHARROW1PIC,            // 47
+	H_FLASHARROW2PIC,            // 48
+	ENDINDG1PIC,                 // 49
+	ENDINDG2PIC,                 // 50
+	ENDINDG3PIC,                 // 51
+	ENDINDG4PIC,                 // 52
+	ENDINDG5PIC,                 // 53
+	ENDINDG6PIC,                 // 54
+	ENDINDG7PIC,                 // 55
+	ENDINDG8PIC,                 // 56
+	ENDINDG9PIC,                 // 57
+	ENDINDG10PIC,                // 58
+	ENDINDG11PIC,                // 59
+	ENDINDG12PIC,                // 60
+	ENDINDG13PIC,                // 61
+	ENDINDG14PIC,                // 62
+	ENDINDG15PIC,                // 63
+	ENDINDG16PIC,                // 64
+	ENDINDG17PIC,                // 65
+	ENDINDG18PIC,                // 66
+	ENDINDG19PIC,                // 67
+	ENDINDG20PIC,                // 68
+	ENDINDG21PIC,                // 69
+	ENDINDG22PIC,                // 70
+	ENDINDG23PIC,                // 71
+	ENDINDG24PIC,                // 72
+	ENDINDG25PIC,                // 73
+	ENDINDG26PIC,                // 74
+	ENDINDG27PIC,                // 75
+	ENDINDG28PIC,                // 76
+	ENDINDG29PIC,                // 77
+	ENDINDG30PIC,                // 78
+	H_IDLOGOPIC,                 // 79
+	H_TOPWINDOWPIC,              // 80
+	H_LEFTWINDOWPIC,             // 81
+	H_RIGHTWINDOWPIC,            // 82
+	H_BOTTOMINFOPIC,             // 83
+	H_BOTTOMWINDOWPIC,           // 84
+	H_BARPIC,                    // 85
+	H_KEEN5PIC,                  // 86
+	H_KEEN6PIC,                  // 87
+
+	START_LUMP(CONTROLS_LUMP_START, __CONTROLSSTART)
+	CP_MAINMENUPIC,              // 88
+	CP_NEWGAMEMENUPIC,           // 89
+	CP_LOADMENUPIC,              // 90
+	CP_SAVEMENUPIC,              // 91
+	CP_CONFIGMENUPIC,            // 92
+	CP_SOUNDMENUPIC,             // 93
+	CP_MUSICMENUPIC,             // 94
+	CP_KEYBOARDMENUPIC,          // 95
+	CP_KEYMOVEMENTPIC,           // 96
+	CP_KEYBUTTONPIC,             // 97
+	CP_JOYSTICKMENUPIC,          // 98
+	CP_OPTIONSMENUPIC,           // 99
+	CP_PADDLEWARPIC,             // 100
+	CP_QUITPIC,                  // 101
+	CP_JOYSTICKPIC,              // 102
+	CP_MENUSCREENPIC,            // 103
+	END_LUMP(CONTROLS_LUMP_END, __CONTROLSEND)
+
+	IDSOFTPIC,                   // 104
+	PROGTEAMPIC,                 // 105
+	ARTISTPIC,                   // 106
+	DIRECTORPIC,                 // 107
+	SW_BACKGROUNDPIC,            // 108
+	TITLEPICPIC,                 // 109
+	ORACLEPIC,                   // 110
+	KEENTALK1PIC,                // 111
+	KEENTALK2PIC,                // 112
+	KEENMADPIC,                  // 113
+	LINDSEYPIC,                  // 114
+	KEENCOUNT1PIC,               // 115
+	KEENCOUNT2PIC,               // 116
+	KEENCOUNT3PIC,               // 117
+	KEENCOUNT4PIC,               // 118
+	KEENCOUNT5PIC,               // 119
+	KEENCOUNT6PIC,               // 120
+
+	//
+	// MASKED PICS
+	//
+
+	CP_MENUMASKPICM,             // 121
+	CORDPICM,                    // 122
+	METALPOLEPICM,               // 123
+
+	//
+	// SPRITES
+	//
+
+	START_LUMP(PADDLE_LUMP_START, __PADDLESTART)
+	PADDLESPR,                   // 124
+	BALLSPR,                     // 125
+	BALL1PIXELTOTHERIGHTSPR,     // 126
+	BALL2PIXELSTOTHERIGHTSPR,    // 127
+	BALL3PIXELSTOTHERIGHTSPR,    // 128
+	END_LUMP(PADDLE_LUMP_END, __PADDLEEND)
+
+	DEMOPLAQUESPR,               // 129
+
+	//player lump:
+	START_LUMP(KEEN_LUMP_START, __KEENSTART)
+	KEENSTANDRSPR,               // 130
+	KEENRUNR1SPR,                // 131
+	KEENRUNR2SPR,                // 132
+	KEENRUNR3SPR,                // 133
+	KEENRUNR4SPR,                // 134
+	KEENJUMPR1SPR,               // 135
+	KEENJUMPR2SPR,               // 136
+	KEENJUMPR3SPR,               // 137
+	KEENSTANDLSPR,               // 138
+	KEENRUNL1SPR,                // 139
+	KEENRUNL2SPR,                // 140
+	KEENRUNL3SPR,                // 141
+	KEENRUNL4SPR,                // 142
+	KEENJUMPL1SPR,               // 143
+	KEENJUMPL2SPR,               // 144
+	KEENJUMPL3SPR,               // 145
+	KEENLOOKUSPR,                // 146
+	KEENWAITR1SPR,               // 147
+	KEENWAITR2SPR,               // 148
+	KEENWAITR3SPR,               // 149
+	KEENSITREAD1SPR,             // 150
+	KEENSITREAD2SPR,             // 151
+	KEENSITREAD3SPR,             // 152
+	KEENSITREAD4SPR,             // 153
+	KEENREAD1SPR,                // 154
+	KEENREAD2SPR,                // 155
+	KEENREAD3SPR,                // 156
+	KEENSTOPREAD1SPR,            // 157
+	KEENSTOPREAD2SPR,            // 158
+	KEENWATCHSPR,                // 159
+	KEENLOOKD1SPR,               // 160
+	KEENLOOKD2SPR,               // 161
+	KEENDIE1SPR,                 // 162
+	KEENDIE2SPR,                 // 163
+	STUNSTARS1SPR,               // 164
+	STUNSTARS2SPR,               // 165
+	STUNSTARS3SPR,               // 166
+	KEENSHOOTLSPR,               // 167
+	KEENJLSHOOTLSPR,             // 168
+	KEENJSHOOTDSPR,              // 169
+	KEENJSHOOTUSPR,              // 170
+	KEENSHOOTUSPR,               // 171
+	KEENSHOOTRSPR,               // 172
+	KEENJRSHOOTRSPR,             // 173
+	STUN1SPR,                    // 174
+	STUN2SPR,                    // 175
+	STUN3SPR,                    // 176
+	STUN4SPR,                    // 177
+	STUNHIT1SPR,                 // 178
+	STUNHIT2SPR,                 // 179
+	KEENSHINNYR1SPR,             // 180
+	KEENSHINNYR2SPR,             // 181
+	KEENSHINNYR3SPR,             // 182
+	KEENSLIDED1SPR,              // 183
+	KEENSLIDED2SPR,              // 184
+	KEENSLIDED3SPR,              // 185
+	KEENSLIDED4SPR,              // 186
+	KEENSHINNYL1SPR,             // 187
+	KEENSHINNYL2SPR,             // 188
+	KEENSHINNYL3SPR,             // 189
+	KEENPLSHOOTUSPR,             // 190
+	KEENPRSHOOTUSPR,             // 191
+	KEENPRSHOOTDSPR,             // 192
+	KEENPLSHOOTDSPR,             // 193
+	KEENPSHOOTLSPR,              // 194
+	KEENPSHOOTRSPR,              // 195
+	KEENENTER1SPR,               // 196
+	KEENENTER2SPR,               // 197
+	KEENENTER3SPR,               // 198
+	KEENENTER4SPR,               // 199
+	KEENENTER5SPR,               // 200
+	KEENHANGLSPR,                // 201
+	KEENHANGRSPR,                // 202
+	KEENCLIMBEDGEL1SPR,          // 203
+	KEENCLIMBEDGEL2SPR,          // 204
+	KEENCLIMBEDGEL3SPR,          // 205
+	KEENCLIMBEDGEL4SPR,          // 206
+	KEENCLIMBEDGER1SPR,          // 207
+	KEENCLIMBEDGER2SPR,          // 208
+	KEENCLIMBEDGER3SPR,          // 209
+	KEENCLIMBEDGER4SPR,          // 210
+	KEENPOGOR1SPR,               // 211
+	KEENPOGOR2SPR,               // 212
+	KEENPOGOL1SPR,               // 213
+	KEENPOGOL2SPR,               // 214
+	DROPSPLASH1SPR,              // 215
+	DROPSPLASH2SPR,              // 216
+	DROPSPLASH3SPR,              // 217
+	BONUS100UPSPR,               // 218
+	BONUS100SPR,                 // 219
+	BONUS200SPR,                 // 220
+	BONUS500SPR,                 // 221
+	BONUS1000SPR,                // 222
+	BONUS2000SPR,                // 223
+	BONUS5000SPR,                // 224
+	BONUS1UPSPR,                 // 225
+	BONUSCLIPSPR,                // 226
+	END_LUMP(KEEN_LUMP_END, __KEENEND)
+
+	START_LUMP(SUGAR1_LUMP_START, __SUGAR1START)
+	SUGAR1ASPR,                  // 227
+	SUGAR1BSPR,                  // 228
+	END_LUMP(SUGAR1_LUMP_END, __SUGAR1END)
+
+	START_LUMP(SUGAR2_LUMP_START, __SUGAR2START)
+	SUGAR2ASPR,                  // 229
+	SUGAR2BSPR,                  // 230
+	END_LUMP(SUGAR2_LUMP_END, __SUGAR2END)
+
+	START_LUMP(SUGAR3_LUMP_START, __SUGAR3START)
+	SUGAR3ASPR,                  // 231
+	SUGAR3BSPR,                  // 232
+	END_LUMP(SUGAR3_LUMP_END, __SUGAR3END)
+
+	START_LUMP(SUGAR4_LUMP_START, __SUGAR4START)
+	SUGAR4ASPR,                  // 233
+	SUGAR4BSPR,                  // 234
+	END_LUMP(SUGAR4_LUMP_END, __SUGAR4END)
+
+	START_LUMP(SUGAR5_LUMP_START, __SUGAR5START)
+	SUGAR5ASPR,                  // 235
+	SUGAR5BSPR,                  // 236
+	END_LUMP(SUGAR5_LUMP_END, __SUGAR5END)
+
+	START_LUMP(SUGAR6_LUMP_START, __SUGAR6START)
+	SUGAR6ASPR,                  // 237
+	SUGAR6BSPR,                  // 238
+	END_LUMP(SUGAR6_LUMP_END, __SUGAR6END)
+
+	START_LUMP(ONEUP_LUMP_START, __ONEUPSTART)
+	ONEUPASPR,                   // 239
+	ONEUPBSPR,                   // 240
+	END_LUMP(ONEUP_LUMP_END, __ONEUPEND)
+
+	DOORSPR,                     // 241
+
+	START_LUMP(KEYGEM_LUMP_START, __KEYGEMSTART)
+	REDGEM1SPR,                  // 242
+	REDGEM2SPR,                  // 243
+	YELLOWGEM1SPR,               // 244
+	YELLOWGEM2SPR,               // 245
+	BLUEGEM1SPR,                 // 246
+	BLUEGEM2SPR,                 // 247
+	GREENGEM1SPR,                // 248
+	GREENGEM2SPR,                // 249
+	BONUSGEMSPR,                 // 250
+	END_LUMP(KEYGEM_LUMP_END, __KEYGEMEND)
+
+	START_LUMP(AMMO_LUMP_START, __AMMOSTART)
+	STUNCLIP1SPR,                // 251
+	STUNCLIP2SPR,                // 252
+	END_LUMP(AMMO_LUMP_END, __AMMOEND)
+
+	SCOREBOXSPR,                 // 253
+
+	START_LUMP(WORLDKEEN_LUMP_START, __WORLDKEENSTART)
+	WORLDKEENL1SPR,              // 254
+	WORLDKEENL2SPR,              // 255
+	WORLDKEENL3SPR,              // 256
+	WORLDKEENR1SPR,              // 257
+	WORLDKEENR2SPR,              // 258
+	WORLDKEENR3SPR,              // 259
+	WORLDKEENU1SPR,              // 260
+	WORLDKEENU2SPR,              // 261
+	WORLDKEENU3SPR,              // 262
+	WORLDKEEND1SPR,              // 263
+	WORLDKEEND2SPR,              // 264
+	WORLDKEEND3SPR,              // 265
+	WORLDKEENDR1SPR,             // 266
+	WORLDKEENDR2SPR,             // 267
+	WORLDKEENDR3SPR,             // 268
+	WORLDKEENDL1SPR,             // 269
+	WORLDKEENDL2SPR,             // 270
+	WORLDKEENDL3SPR,             // 271
+	WORLDKEENUL1SPR,             // 272
+	WORLDKEENUL2SPR,             // 273
+	WORLDKEENUL3SPR,             // 274
+	WORLDKEENUR1SPR,             // 275
+	WORLDKEENUR2SPR,             // 276
+	WORLDKEENUR3SPR,             // 277
+	WORLDKEENWAVE1SPR,           // 278
+	WORLDKEENWAVE2SPR,           // 279
+	WORLDKEENSWIMU1SPR,          // 280
+	WORLDKEENSWIMU2SPR,          // 281
+	WORLDKEENSWIMR1SPR,          // 282
+	WORLDKEENSWIMR2SPR,          // 283
+	WORLDKEENSWIMD1SPR,          // 284
+	WORLDKEENSWIMD2SPR,          // 285
+	WORLDKEENSWIML1SPR,          // 286
+	WORLDKEENSWIML2SPR,          // 287
+	WORLDKEENSWIMUR1SPR,         // 288
+	WORLDKEENSWIMUR2SPR,         // 289
+	WORLDKEENSWIMDR1SPR,         // 290
+	WORLDKEENSWIMDR2SPR,         // 291
+	WORLDKEENSWIMDL1SPR,         // 292
+	WORLDKEENSWIMDL2SPR,         // 293
+	WORLDKEENSWIMUL1SPR,         // 294
+	WORLDKEENSWIMUL2SPR,         // 295
+	WOLRDKEENRIDE1SPR,           // 296
+	WOLRDKEENRIDE2SPR,           // 297
+	FLAGFLIP1SPR,                // 298
+	FLAGFLIP2SPR,                // 299
+	FLAGFLIP3SPR,                // 300
+	FLAGFLIP4SPR,                // 301
+	FLAGFLIP5SPR,                // 302
+	FLAGFALL1SPR,                // 303
+	FLAGFALL2SPR,                // 304
+	FLAGFLAP1SPR,                // 305
+	FLAGFLAP2SPR,                // 306
+	FLAGFLAP3SPR,                // 307
+	FLAGFLAP4SPR,                // 308
+	END_LUMP(WORLDKEEN_LUMP_END, __WORLDKEENEND)
+
+	START_LUMP(SCUBAKEEN_LUMP_START, __SCUBAKEENSTART)
+	SCUBAKEENL1SPR,              // 309
+	SCUBAKEENL2SPR,              // 310
+	SCUBAKEENR1SPR,              // 311
+	SCUBAKEENR2SPR,              // 312
+	SCUBAKEENDEAD1SPR,           // 313
+	SCUBAKEENDEAD2SPR,           // 314
+	END_LUMP(SCUBAKEEN_LUMP_END, __SCUBAKEENEND)
+
+	START_LUMP(SLUG_LUMP_START, __SLUGSTART)
+	SLUGWALKR1SPR,               // 315
+	SLUGWALKR2SPR,               // 316
+	SLUGPISSRSPR,                 // 317
+	SLUGSTUN1SPR,             // 318
+	SLUGSTUN2SPR,             // 319
+	SLUGWALKL1SPR,               // 320
+	SLUGWALKL2SPR,               // 321
+	SLUGPISSLSPR,                 // 322
+	SLUGSLIME1SPR,               // 323
+	SLUGSLIME2SPR,               // 324
+	END_LUMP(SLUG_LUMP_END, __SLUGEND)
+
+	START_LUMP(MADMUSHROOM_LUMP_START, __MADMUSHROOMSTART)
+	MADMUSHROOML1SPR,            // 325
+	MADMUSHROOML2SPR,            // 326
+	MADMUSHROOMR1SPR,            // 327
+	MADMUSHROOMR2SPR,            // 328
+	END_LUMP(MADMUSHROOM_LUMP_END, __MADMUSHROOMEND)
+
+	START_LUMP(LINDSEY_LUMP_START, __LINDSEYSTART)
+	LINDSEY1SPR,                 // 329
+	LINDSEY2SPR,                 // 330
+	LINDSEY3SPR,                 // 331
+	LINDSEY4SPR,                 // 332
+	END_LUMP(LINDSEY_LUMP_END, __LINDSEYEND)
+
+	START_LUMP(INCHWORM_LUMP_START, __INCHWORMSTART)
+	INCHWORMR1SPR,               // 333
+	INCHWORMR2SPR,               // 334
+	INCHWORML1SPR,               // 335
+	INCHWORML2SPR,               // 336
+	FOOTSPR,                     // 337
+	END_LUMP(INCHWORM_LUMP_END, __INCHWORMEND)
+
+	START_LUMP(EATER_LUMP_START, __EATERSTART)
+	EATERSTAND1SPR,              // 338
+	EATERSTAND2SPR,              // 339
+	EATERJUMPR1SPR,              // 340
+	EATERJUMPR2SPR,              // 341
+	EATERJUMPR3SPR,              // 342
+	EATERJUMPL1SPR,              // 343
+	EATERJUMPL2SPR,              // 344
+	EATERJUMPL3SPR,              // 345
+	EATENBONUS1SPR,              // 346
+	EATENBONUS2SPR,              // 347
+	EATENBONUS3SPR,              // 348
+	EATENBONUS4SPR,              // 349
+	SMOKE1SPR,                   // 350
+	SMOKE2SPR,                   // 351
+	SMOKE3SPR,                   // 352
+	SMOKE4SPR,                   // 353
+	SMOKE5SPR,                   // 354
+	EATERSTUNSPR,                // 355
+	END_LUMP(EATER_LUMP_END, __EATEREND)
+
+	START_LUMP(COUNCIL_LUMP_START, __COUINCILSTART)
+	COUNCILWALKR1SPR,            // 356
+	COUNCILWALKR2SPR,            // 357
+	COUNCILWALKL1SPR,            // 358
+	COUNCILWALKL2SPR,            // 359
+	COUNCILTHINKLSPR,            // 360
+	COUNCILTHINKRSPR,            // 361
+	END_LUMP(COUNCIL_LUMP_END, __COUNCILEND)
+
+	START_LUMP(EGG_LUMP_START, __EGGSTART)
+	EGGSPR,                      // 362
+	EGGBROKESPR,                // 363
+	EGGCHIP1SPR,                // 364
+	EGGCHIP2SPR,                // 365
+	EGGCHIP3SPR,                // 366
+	END_LUMP(EGG_LUMP_END, __EGGEND)
+
+	START_LUMP(EGGBIRD_LUMP_START, __EGGBIRDSTART)
+	BIRDWALKR1SPR,               // 367
+	BIRDWALKR2SPR,               // 368
+	BIRDWALKR3SPR,               // 369
+	BIRDWALKR4SPR,               // 370
+	BIRDWALKL1SPR,               // 371
+	BIRDWALKL2SPR,               // 372
+	BIRDWALKL3SPR,               // 373
+	BIRDWALKL4SPR,               // 374
+	BIRDFLY1SPR,                 // 375
+	BIRDFLY2SPR,                 // 376
+	BIRDFLY3SPR,                 // 377
+	BIRDFLY4SPR,                 // 378
+	BIRDSTUNSPR,                 // 379
+	END_LUMP(EGGBIRD_LUMP_END, __EGGBIRDEND)
+
+	START_LUMP(DARTS_LUMP_START, __DARTSSTART)
+	DARTU1SPR,                   // 380
+	DARTU2SPR,                   // 381
+	DARTD1SPR,                   // 382
+	DARTD2SPR,                   // 383
+	DARTR1SPR,                   // 384
+	DARTR2SPR,                   // 385
+	DARTL1SPR,                   // 386
+	DARTL2SPR,                   // 387
+	END_LUMP(DARTS_LUMP_END, __DARTSEND)
+
+	START_LUMP(MIMROCK_LUMP_START, __MIMROCKSTART)
+	MIMROCKSPR,                  // 388
+	MIMROCKWALKL1SPR,            // 389
+	MIMROCKWALKL2SPR,            // 390
+	MIMROCKWALKL3SPR,            // 391
+	MIMROCKWALKL4SPR,            // 392
+	MIMROCKWALKR1SPR,            // 393
+	MIMROCKWALKR2SPR,            // 394
+	MIMROCKWALKR3SPR,            // 395
+	MIMROCKWALKR4SPR,            // 396
+	MIMROCKJUMPR1SPR,            // 397
+	MIMROCKJUMPR2SPR,            // 398
+	MIMROCKJUMPR3SPR,            // 399
+	MIMROCKJUMPL1SPR,            // 400
+	MIMROCKJUMPL2SPR,            // 401
+	MIMROCKJUMPL3SPR,            // 402
+	MINROCKSTUNSPR,              // 403
+	END_LUMP(MIMROCK_LUMP_END, __MIMROCKEND)
+
+	START_LUMP(DOPEFISH_LUMP_START, __DOPEFISHSTART)
+	DOPEFISHSWIMR1SPR,           // 404
+	DOPEFISHSWIMR2SPR,           // 405
+	DOPEFISHHUNGRYRSPR,          // 406
+	DOPEFISHBURP1SPR,            // 407
+	DOPEFISHBURP2SPR,            // 408
+	BIGBUBBLE1SPR,               // 409
+	BIGBUBBLE2SPR,               // 410
+	BIGBUBBLE3SPR,               // 411
+	BIGBUBBLE4SPR,               // 412
+	SMALLBUBBLE1SPR,             // 413
+	SMALLBUBBLE2SPR,             // 414
+	SMALLBUBBLE3SPR,             // 415
+	SMALLBUBBLE4SPR,             // 416
+	MEDIUMBUBBLESPR,             // 417
+	DOPEFISHSWIML1SPR,           // 418
+	DOPEFISHSWIML2SPR,           // 419
+	DOPEFISHHUNGRYLSPR,          // 420
+	END_LUMP(DOPEFISH_LUMP_END, __DOPEFISHEND)
+
+	START_LUMP(SCHOOLFISH_LUMP_START, __SCHOOLFISHSTART)
+	SCHOOLFISHL1SPR,             // 421
+	SCHOOLFISHL2SPR,             // 422
+	SCHOOLFISHR1SPR,             // 423
+	SCHOOLFISHR2SPR,             // 424
+	END_LUMP(SCHOOLFISH_LUMP_END, __SCHOOLFISHEND)
+
+	START_LUMP(ARACHNUT_LUMP_START, __ARACHNUTSTART)
+	ARACHNUTWALK1SPR,            // 425
+	ARACHNUTWALK2SPR,            // 426
+	ARACHNUTWALK3SPR,            // 427
+	ARACHNUTWALK4SPR,            // 428
+	ARACHNUTSTUNSPR,             // 429
+	END_LUMP(ARACHNUT_LUMP_END, __ARACHNUTEND)
+
+	SCUBASPR,                    // 430
+
+	START_LUMP(SPRITE_LUMP_START, __SPRITESTART)
+	SPRITEFLOATSPR,              // 431
+	SPRITEAIMLSPR,               // 432
+	SPRITESHOOTLSPR,             // 433
+	SPRITEAIMRSPR,               // 434
+	SPRITESHOOTRSPR,             // 435
+	SPRITESHOT1SPR,              // 436
+	SPRITESHOT2SPR,              // 437
+	SPRITESHOT3SPR,              // 438
+	SPRITESHOT4SPR,              // 439
+	END_LUMP(SPRITE_LUMP_END, __SPRITEEND)
+
+	START_LUMP(MINE_LUMP_START, __MINESTART)
+	MINESPR,                     // 440
+	MINEEXPLODE1SPR,             // 441
+	MINEEXPLODE2SPR,             // 442
+	END_LUMP(MINE_LUMP_END, __MINEEND)
+
+	START_LUMP(SKYPEST_LUMP_START, __SKYPESTSTART)
+	SKYPESTFLYL1SPR,             // 443
+	SKYPESTFLYL2SPR,             // 444
+	SKYPESTFLYR1SPR,             // 445
+	SKYPESTFLYR2SPR,             // 446
+	SKYPESTSIT1SPR,              // 447
+	SKYPESTSIT2SPR,              // 448
+	SKYPESTSIT3SPR,              // 449
+	SKYPESTSIT4SPR,              // 450
+	SKYPESTSIT5SPR,              // 451
+	SKYPESTSIT6SPR,              // 452
+	SKYPESTSIT7SPR,              // 453
+	SKYPESTSIT8SPR,              // 454
+	SKYPESTSIT9SPR,              // 455
+	SKYPESTSQUASHEDSPR,          // 456
+	END_LUMP(SKYPEST_LUMP_END, __SKYPESTEND)
+
+	START_LUMP(WORMOUTH_LUMP_START, __WORMOUTHSTART)
+	WORMOUTHSPR,                 // 457
+	WORMOUTHPEEKR1SPR,           // 458
+	WORMOUTHPEEKR2SPR,           // 459
+	WORMOUTHPEEKL1SPR,           // 460
+	WORMOUTHPEEKL2SPR,           // 461
+	WORMOUTHBITER1SPR,           // 462
+	WORMOUTHBITER2SPR,           // 463
+	WORMOUTHBITER3SPR,           // 464
+	WORMOUTHBITEL1SPR,           // 465
+	WORMOUTHBITEL2SPR,           // 466
+	WORMOUTHBITEL3SPR,           // 467
+	WORMOUTHSTUNSPR,             // 468
+	END_LUMP(WORMOUTH_LUMP_END, __WORMOUTHEND)
+
+	START_LUMP(LICK_LUMP_START, __LICKSTART)
+	LICKMOVER1SPR,               // 469
+	LICKMOVER2SPR,               // 470
+	LICKMOVER3SPR,               // 471
+	LICKMOVER4SPR,               // 472
+	LICKMOVEL1SPR,               // 473
+	LICKMOVEL2SPR,               // 474
+	LICKMOVEL3SPR,               // 475
+	LICKMOVEL4SPR,               // 476
+	LICKATTACKR1SPR,             // 477
+	LICKATTACKR2SPR,             // 478
+	LICKATTACKR3SPR,             // 479
+	LICKATTACKL1SPR,             // 480
+	LICKATTACKL2SPR,             // 481
+	LICKATTACKL3SPR,             // 482
+	LICKSTUNSPR,                 // 483
+	END_LUMP(LICK_LUMP_END, __LICKEND)
+
+	START_LUMP(PLATFORM_LUMP_START, __PLATFORMSTART)
+	PLATFORMSPR,                 // 484
+	PLATSIDETHRUST1SPR,          // 485
+	PLATSIDETHRUST2SPR,          // 486
+	PLATRTHRUST1SPR,             // 487
+	PLATRTHRUST2SPR,             // 488
+	PLATLTHRUST1SPR,             // 489
+	PLATLTHRUST2SPR,             // 490
+	END_LUMP(PLATFORM_LUMP_END, __PLATFORMEND)
+
+	START_LUMP(BOUNDER_LUMP_START, __BOUNDERSTART)
+	BOUNDERL1SPR,                // 491
+	BOUNDERL2SPR,                // 492
+	BOUNDERR1SPR,                // 493
+	BOUNDERR2SPR,                // 494
+	BOUNDERC1SPR,                // 495
+	BOUNDERC2SPR,                // 496
+	BOUNDERSTUNSPR,           // 497
+	END_LUMP(BOUNDER_LUMP_END, __BOUNDEREND)
+
+	START_LUMP(THUNDERCLOUD_LUMP_START, __THUNDERCLOUDSTART)
+	CLOUDSPR,                    // 498
+	CLOUDACTIVESPR,              // 499
+	CLOUDCHARGESPR,              // 500
+	BOLT1SPR,               // 501
+	BOLT2SPR,               // 502
+	END_LUMP(THUNDERCLOUD_LUMP_END, __THUNDERCLOUDEND)
+
+	START_LUMP(BERKELOID_LUMP_START, __BERKELOIDSTART)
+	BERKEWALKL1SPR,              // 503
+	BERKEWALKL2SPR,              // 504
+	BERKEWALKL3SPR,              // 505
+	BERKEWALKL4SPR,              // 506
+	BERKEWALKR1SPR,              // 507
+	BERKEWALKR2SPR,              // 508
+	BERKEWALKR3SPR,              // 509
+	BERKEWALKR4SPR,              // 510
+	BERKETHROWL1SPR,             // 511
+	BERKETHROWL2SPR,             // 512
+	BERKETHROWR1SPR,             // 513
+	BERKETHROWR2SPR,             // 514
+	FIREBALL1SPR,                // 515
+	FIREBALL2SPR,                // 516
+	FIREBALL3SPR,                // 517
+	FIREBALL4SPR,                // 518
+	END_LUMP(BERKELOID_LUMP_END, __BERKELOIDEND)
+
+	START_LUMP(MOON_LUMP_START, __MOONSTART)
+	KEENMOON1SPR,                // 519
+	KEENMOON2SPR,                // 520
+	END_LUMP(MOON_LUMP_END, __MOONEND)
+
+	//
+	// TILES (these don't need names)
+	//
+
+	LASTTILE=STARTEXTERNS-1,
+
+	//
+	// EXTERNS
+	//
+
+	ORDERSCREEN,                 // 4735
+	BIGCOMMANDER,                // 4736
+	BIGKEEN,                     // 4737
+	OUTOFMEM,                    // 4738
+
+	//texts
+	T_HELPART,                   // 4739
+	T_STORYART,                  // 4740
+	T_CONTRART,                  // 4741
+	T_IDART,                     // 4742
+	T_ENDART,                    // 4743
+	T_DEMOART,                   // 4744
+	T_ORDERART,                  // 4745
+
+	//demos
+	DEMO0,                       // 4746
+	DEMO1,                       // 4747
+	DEMO2,                       // 4748
+	DEMO3,                       // 4749
+	DEMO4,                       // 4750
+
+	NUMGRCHUNKS
+} graphicnums;
+
+#undef START_LUMP
+#undef END_LUMP
+
+#endif //__GFX_H__
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/KEEN4/ID_ASM.EQU b/16/keen456/KEEN4-6/KEEN4/ID_ASM.EQU
new file mode 100755
index 00000000..6f755671
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN4/ID_ASM.EQU
@@ -0,0 +1,115 @@
+;
+; Equates for all .ASM files
+;
+
+;----------------------------------------------------------------------------
+
+INCLUDE	"GFXE_CK4.EQU"
+
+;----------------------------------------------------------------------------
+
+CGAGR		=	1
+EGAGR		=	2
+VGAGR		=	3
+
+GRMODE		=	EGAGR
+PROFILE		=	0			; 1=keep stats on tile drawing
+
+SC_INDEX	=	03C4h
+SC_RESET	=	0
+SC_CLOCK	=	1
+SC_MAPMASK	=	2
+SC_CHARMAP	=	3
+SC_MEMMODE	=	4
+
+CRTC_INDEX	=	03D4h
+CRTC_H_TOTAL	=	0
+CRTC_H_DISPEND	=	1
+CRTC_H_BLANK	=	2
+CRTC_H_ENDBLANK	=	3
+CRTC_H_RETRACE	=	4
+CRTC_H_ENDRETRACE =	5
+CRTC_V_TOTAL	=	6
+CRTC_OVERFLOW	=	7
+CRTC_ROWSCAN	=	8
+CRTC_MAXSCANLINE =	9
+CRTC_CURSORSTART =	10
+CRTC_CURSOREND	=	11
+CRTC_STARTHIGH	=	12
+CRTC_STARTLOW	=	13
+CRTC_CURSORHIGH	=	14
+CRTC_CURSORLOW	=	15
+CRTC_V_RETRACE	=	16
+CRTC_V_ENDRETRACE =	17
+CRTC_V_DISPEND	=	18
+CRTC_OFFSET	=	19
+CRTC_UNDERLINE	=	20
+CRTC_V_BLANK	=	21
+CRTC_V_ENDBLANK	=	22
+CRTC_MODE	=	23
+CRTC_LINECOMPARE =	24
+
+
+GC_INDEX	=	03CEh
+GC_SETRESET	=	0
+GC_ENABLESETRESET =	1
+GC_COLORCOMPARE	=	2
+GC_DATAROTATE	=	3
+GC_READMAP	=	4
+GC_MODE		=	5
+GC_MISCELLANEOUS =	6
+GC_COLORDONTCARE =	7
+GC_BITMASK	=	8
+
+ATR_INDEX	=	03c0h
+ATR_MODE	=	16
+ATR_OVERSCAN	=	17
+ATR_COLORPLANEENABLE =	18
+ATR_PELPAN	=	19
+ATR_COLORSELECT	=	20
+
+STATUS_REGISTER_1     =	03dah
+
+
+MACRO	WORDOUT
+	out	dx,ax
+ENDM
+
+if 0
+
+MACRO	WORDOUT
+	out	dx,al
+	inc	dx
+	xchg	al,ah
+	out	dx,al
+	dec	dx
+	xchg	al,ah
+ENDM
+
+endif
+
+UPDATEWIDE	=	22
+UPDATEHIGH	=	14
+
+;
+; tile info offsets from segment tinf
+;
+
+ANIM		=	402
+SPEED		=	(ANIM+NUMTILE16)
+
+NORTHWALL	=	(SPEED+NUMTILE16)
+EASTWALL	=	(NORTHWALL+NUMTILE16M)
+SOUTHWALL   =	(EASTWALL+NUMTILE16M)
+WESTWALL    =	(SOUTHWALL+NUMTILE16M)
+MANIM       =	(WESTWALL+NUMTILE16M)
+INTILE      =	(MANIM+NUMTILE16M)
+MSPEED      =	(INTILE+NUMTILE16M)
+
+
+IFE GRMODE-EGAGR
+SCREENWIDTH	=	64
+ENDIF
+IFE GRMODE-CGAGR
+SCREENWIDTH	=	128
+ENDIF
diff --git a/16/keen456/KEEN4-6/KEEN4/ID_HEADS.H b/16/keen456/KEEN4-6/KEEN4/ID_HEADS.H
new file mode 100755
index 00000000..1c42a6b6
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN4/ID_HEADS.H
@@ -0,0 +1,109 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+// ID_GLOB.H
+
+
+#include <ALLOC.H>
+#include <CTYPE.H>
+#include <DOS.H>
+#include <ERRNO.H>
+#include <FCNTL.H>
+#include <IO.H>
+#include <MEM.H>
+#include <PROCESS.H>
+#include <STDIO.H>
+#include <STDLIB.H>
+#include <STRING.H>
+#include <SYS\STAT.H>
+
+#define __ID_GLOB__
+
+//--------------------------------------------------------------------------
+
+#define KEEN
+#define KEEN4
+
+#define	EXTENSION	"CK4"
+
+extern	char far introscn;
+
+#include "GFXE_CK4.H"
+#include "AUDIOCK4.H"
+
+//--------------------------------------------------------------------------
+
+#define	TEXTGR	0
+#define	CGAGR	1
+#define	EGAGR	2
+#define	VGAGR	3
+
+#define GRMODE	EGAGR
+
+#if GRMODE == EGAGR
+#define GREXT	"EGA"
+#endif
+#if GRMODE == CGAGR
+#define GREXT	"CGA"
+#endif
+
+//#define PROFILE
+
+//
+//	ID Engine
+//	Types.h - Generic types, #defines, etc.
+//	v1.0d1
+//
+
+#ifndef	__TYPES__
+#define	__TYPES__
+
+typedef	enum	{false,true}	boolean;
+typedef	unsigned	char		byte;
+typedef	unsigned	int			word;
+typedef	unsigned	long		longword;
+typedef	byte *					Ptr;
+
+typedef	struct
+		{
+			int	x,y;
+		} Point;
+typedef	struct
+		{
+			Point	ul,lr;
+		} Rect;
+
+#define	nil	((void *)0)
+
+#endif
+
+#include "ID_MM.H"
+#include "ID_CA.H"
+#include "ID_VW.H"
+#include "ID_RF.H"
+#include "ID_IN.H"
+#include "ID_SD.H"
+#include "ID_US.H"
+
+
+void	Quit (char *error);		// defined in user program
+
diff --git a/16/keen456/KEEN4-6/KEEN4/K4_ACT1.C b/16/keen456/KEEN4-6/KEEN4/K4_ACT1.C
new file mode 100755
index 00000000..f26104b1
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN4/K4_ACT1.C
@@ -0,0 +1,1221 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+/*
+K4_ACT1.C
+=========
+
+Contains the following actor types (in this order):
+
+- Miragia (world map)
+- Bonus Items
+- Council Member
+- Poison Slug
+- Mad Mushroom
+- Egg & Eggbird
+- Arachnut
+- Skypest
+
+*/
+
+#include "CK_DEF.H"
+
+/*
+=============================================================================
+
+						  MIRAGIA
+
+=============================================================================
+*/
+
+statetype s_miragia0 = {0, 0, step, false, false, 300, 0, 0, T_Miragia0, NULL, NULL, &s_miragia1};
+statetype s_miragia1 = {0, 0, step, false, false,  30, 0, 0, T_Miragia1, NULL, NULL, &s_miragia2};
+statetype s_miragia2 = {0, 0, step, false, false,  30, 0, 0, T_Miragia2, NULL, NULL, &s_miragia3};
+statetype s_miragia3 = {0, 0, step, false, false,  30, 0, 0, T_Miragia3, NULL, NULL, &s_miragia4};
+statetype s_miragia4 = {0, 0, step, false, false, 300, 0, 0, T_Miragia4, NULL, NULL, &s_miragia5};
+statetype s_miragia5 = {0, 0, step, false, false,  30, 0, 0, T_Miragia5, NULL, NULL, &s_miragia6};
+statetype s_miragia6 = {0, 0, step, false, false,  30, 0, 0, T_Miragia6, NULL, NULL, &s_miragia7};
+statetype s_miragia7 = {0, 0, step, false, false,  30, 0, 0, T_Miragia7, NULL, NULL, &s_miragia0};
+
+/*
+===========================
+=
+= SpawnMiragia
+=
+===========================
+*/
+
+void SpawnMiragia(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = inertobj;
+	new->active = ac_allways;
+	new->x = x;
+	new->y = y;
+	new->state = &s_miragia0;
+}
+
+/*
+===========================
+=
+= T_Miragia0
+=
+===========================
+*/
+
+void T_Miragia0(objtype *ob)
+{
+	if (player->tileright >= ob->x && player->tileleft <= ob->x+5
+		&& player->tiletop >= ob->y && player->tilebottom <= ob->y+4)
+	{
+		//don't let miragia appear if player is in the area, so player won't get stuck
+		ob->state = &s_miragia7;
+	}
+	else
+	{
+		RF_MapToMap(8, 60, ob->x, ob->y, 6, 4);
+	}
+}
+
+/*
+===========================
+=
+= T_Miragia1
+=
+===========================
+*/
+
+void T_Miragia1(objtype *ob)
+{
+	RF_MapToMap(14, 60, ob->x, ob->y, 6, 4);
+}
+
+/*
+===========================
+=
+= T_Miragia2
+=
+===========================
+*/
+
+void T_Miragia2(objtype *ob)
+{
+	RF_MapToMap(20, 60, ob->x, ob->y, 6, 4);
+}
+
+/*
+===========================
+=
+= T_Miragia3
+=
+===========================
+*/
+
+void T_Miragia3(objtype *ob)
+{
+	RF_MapToMap(26, 60, ob->x, ob->y, 6, 4);
+}
+
+/*
+===========================
+=
+= T_Miragia4
+=
+===========================
+*/
+
+void T_Miragia4(objtype *ob)
+{
+	RF_MapToMap(20, 60, ob->x, ob->y, 6, 4);
+}
+
+/*
+===========================
+=
+= T_Miragia5
+=
+===========================
+*/
+
+void T_Miragia5(objtype *ob)
+{
+	RF_MapToMap(14, 60, ob->x, ob->y, 6, 4);
+}
+
+/*
+===========================
+=
+= T_Miragia6
+=
+===========================
+*/
+
+void T_Miragia6(objtype *ob)
+{
+	RF_MapToMap(8, 60, ob->x, ob->y, 6, 4);
+}
+
+/*
+===========================
+=
+= T_Miragia7
+=
+===========================
+*/
+
+void T_Miragia7(objtype *ob)
+{
+	RF_MapToMap(2, 60, ob->x, ob->y, 6, 4);
+}
+
+/*
+=============================================================================
+
+						  BONUS ITEMS
+
+temp1 = bonus type
+temp2 = base shape number
+temp3 = last animated shape number +1
+
+=============================================================================
+*/
+
+statetype s_bonus1 = {0, 0, step, false, false, 20, 0, 0, T_Bonus, NULL, R_Draw, &s_bonus2};
+statetype s_bonus2 = {0, 0, step, false, false, 20, 0, 0, T_Bonus, NULL, R_Draw, &s_bonus1};
+statetype s_bonusrise = {0, 0, slide, false, false, 40, 0, 8, NULL, NULL, R_Draw, NULL};
+
+statetype s_splash1 = {DROPSPLASH1SPR, DROPSPLASH1SPR, step, false, false, 10, 0, 0, NULL, NULL, R_Draw, &s_splash2};
+statetype s_splash2 = {DROPSPLASH2SPR, DROPSPLASH2SPR, step, false, false, 10, 0, 0, NULL, NULL, R_Draw, &s_splash3};
+statetype s_splash3 = {DROPSPLASH3SPR, DROPSPLASH3SPR, step, false, false, 10, 0, 0, NULL, NULL, R_Draw, NULL};
+
+Uint16 bonusshape[] = {REDGEM1SPR, YELLOWGEM1SPR, BLUEGEM1SPR, GREENGEM1SPR, SUGAR1ASPR, SUGAR2ASPR, SUGAR3ASPR, SUGAR4ASPR, SUGAR5ASPR, SUGAR6ASPR, ONEUPASPR, STUNCLIP1SPR};
+
+/*
+===========================
+=
+= SpawnBonus
+=
+===========================
+*/
+
+void SpawnBonus(Sint16 x, Sint16 y, Sint16 type)
+{
+	GetNewObj(false);
+	new->needtoclip = cl_noclip;
+	new->priority = 2;
+	new->obclass = bonusobj;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y);
+	new->ydir = -1;
+	new->temp1 = type;
+	new->temp2 = new->shapenum = bonusshape[type];
+	new->temp3 = new->temp2 + 2;
+	NewState(new, &s_bonus1);
+}
+
+/*
+===========================
+=
+= SpawnSplash
+=
+===========================
+*/
+
+void SpawnSplash(Sint16 x, Sint16 y)
+{
+	GetNewObj(true);
+	new->needtoclip = cl_noclip;
+	new->priority = 3;
+	new->obclass = inertobj;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y);
+	NewState(new, &s_splash1);
+}
+
+/*
+===========================
+=
+= T_Bonus
+=
+===========================
+*/
+
+void T_Bonus(objtype *ob)
+{
+	ob->shapenum++;
+	if (ob->shapenum == ob->temp3)
+		ob->shapenum = ob->temp2;
+}
+
+/*
+=============================================================================
+
+						  COUNCIL MEMBER
+
+=============================================================================
+*/
+
+statetype s_councilwalk1 = {COUNCILWALKL1SPR, COUNCILWALKR1SPR, step, false, true,   10,  64, 0, T_Council, NULL, R_Walk, &s_councilwalk2};
+statetype s_councilwalk2 = {COUNCILWALKL2SPR, COUNCILWALKR2SPR, step, false, true,   10,  64, 0, T_Council, NULL, R_Walk, &s_councilwalk1};
+statetype s_councilstand = {COUNCILTHINKLSPR, COUNCILTHINKRSPR, step, false, false, 120, 128, 0, NULL, NULL, R_Draw, &s_councilwalk1};
+
+/*
+===========================
+=
+= SpawnCouncil
+=
+===========================
+*/
+
+void SpawnCouncil(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = oracleobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y) -0x171;	//TODO: wierd
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	NewState(new, &s_councilwalk1);
+}
+
+/*
+===========================
+=
+= T_Council
+=
+===========================
+*/
+
+void T_Council(objtype *ob)
+{
+	Uint16 randnum;
+
+	randnum = US_RndT();
+	if (tics*8 > randnum)
+	{
+		// BUG: might be about to move off a ledge, causing it to get stuck
+		// after standing (the stand state doesn't use R_Walk)!
+		// To avoid that, set xtry to 0 here.
+		ob->state = &s_councilstand;
+	}
+}
+
+/*
+=============================================================================
+
+						  POINSON SLUG
+
+=============================================================================
+*/
+
+statetype s_slugwalk1   = {SLUGWALKL1SPR,   SLUGWALKR1SPR,   step,  false, true,    8, 64, 0, NULL, C_Slug, R_WalkNormal, &s_slugwalk2};
+statetype s_slugwalk2   = {SLUGWALKL2SPR,   SLUGWALKR2SPR,   step,  false, true,    8, 64, 0, T_Slug, C_Slug, R_WalkNormal, &s_slugwalk1};
+statetype s_slugpiss1   = {SLUGPISSLSPR,    SLUGPISSRSPR,    step,  false, true,   60, 64, 0, T_SlugPiss, C_Slug, R_WalkNormal, &s_slugwalk1};
+statetype s_slugstun    = {SLUGSTUN1SPR,    SLUGSTUN1SPR,    think, false, false,   0,  0, 0, T_Projectile, NULL, R_Stunned, NULL};
+statetype s_slugstunalt = {SLUGSTUN2SPR,    SLUGSTUN2SPR,    think, false, false,   0,  0, 0, T_Projectile, NULL, R_Stunned, NULL};
+statetype s_slugslime   = {SLUGSLIME1SPR,   SLUGSLIME1SPR,   step,  false, false, 300,  0, 0, NULL, C_Lethal, R_Draw, &s_slugslime2};
+statetype s_slugslime2  = {SLUGSLIME2SPR,   SLUGSLIME2SPR,   step,  false, false,  60,  0, 0, NULL, NULL, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnSlug
+=
+===========================
+*/
+
+void SpawnSlug(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = slugobj;
+	new->active = ac_yes;
+	new->priority = 2;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y) - 0x71;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	NewState(new, &s_slugwalk1);
+}
+
+/*
+===========================
+=
+= T_Slug
+=
+===========================
+*/
+
+void T_Slug(objtype *ob)
+{
+	if (US_RndT() < 16)
+	{
+		if (ob->x < player->x)
+		{
+			ob->xdir = 1;
+		}
+		else
+		{
+			ob->xdir = -1;
+		}
+		ob->state = &s_slugpiss1;
+		SD_PlaySound(SND_SLUGPOO);
+		// Note: might be a good idea to set xtry to 0 here
+	}
+}
+
+/*
+===========================
+=
+= T_SlugPiss
+=
+===========================
+*/
+
+void T_SlugPiss(objtype *ob)
+{
+	GetNewObj(true);
+	new->obclass = inertobj;
+	new->active = ac_removable;
+	new->priority = 0;
+	new->x = ob->x;
+	new->y = ob->bottom - 8*PIXGLOBAL;
+	NewState(new, &s_slugslime);
+}
+
+/*
+===========================
+=
+= C_Slug
+=
+===========================
+*/
+
+void C_Slug(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+	else if (hit->obclass == stunshotobj)
+	{
+		if (US_RndT() < 0x80)
+		{
+			StunObj(ob, hit, &s_slugstun);
+		}
+		else
+		{
+			StunObj(ob, hit, &s_slugstunalt);
+		}
+		ob->yspeed = -24;
+		ob->xspeed = ob->xdir*8;
+	}
+}
+
+/*
+=============================================================================
+
+						  MAD MUSHROOM
+
+temp1 = jump counter
+
+=============================================================================
+*/
+
+statetype s_mushroom1 = {MADMUSHROOML1SPR, MADMUSHROOMR1SPR, stepthink, false, false, 8, 0, 0, T_Mushroom, C_Mushroom, R_Mushroom, &s_mushroom2};
+statetype s_mushroom2 = {MADMUSHROOML2SPR, MADMUSHROOMR2SPR, stepthink, false, false, 8, 0, 0, T_Mushroom, C_Mushroom, R_Mushroom, &s_mushroom1};
+
+/*
+===========================
+=
+= SpawnMadMushroom
+=
+===========================
+*/
+
+void SpawnMadMushroom(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = madmushroomobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y) - 0xF1;
+	new->xdir = 1;
+	new->ydir = 1;
+	NewState(new, &s_mushroom1);
+}
+
+/*
+===========================
+=
+= T_Mushroom
+=
+===========================
+*/
+
+void T_Mushroom(objtype *ob)
+{
+	if (player->x < ob->x)
+	{
+		ob->xdir = -1;
+	}
+	else
+	{
+		ob->xdir = 1;
+	}
+
+	// BUG: this might be executed twice during the same frame if the
+	// object's animation/state changed during that frame, causing the
+	// object to move at twice the speed during that frame!
+	// To avoid that, return if ytry is not 0.
+	DoWeakGravity(ob);
+}
+
+/*
+===========================
+=
+= C_Mushroom
+=
+===========================
+*/
+
+void C_Mushroom(objtype *ob, objtype *hit)
+{
+	ob++;			// shut up compiler
+	if (hit->obclass == stunshotobj)
+	{
+		ExplodeShot(hit);
+	}
+	else if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+}
+
+/*
+===========================
+=
+= R_Mushroom
+=
+===========================
+*/
+
+void R_Mushroom(objtype *ob)
+{
+	if (ob->hitsouth)
+		ob->yspeed = 0;
+
+	if (ob->hitnorth)
+	{
+		ob->yspeed = 0;
+		if (++ob->temp1 == 3)
+		{
+			ob->temp1 = 0;
+			ob->yspeed = -68;
+			SD_PlaySound(SND_BOUNCE2);
+		}
+		else
+		{
+			SD_PlaySound(SND_BOUNCE1);
+			ob->yspeed = -40;
+		}
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+=============================================================================
+
+						  EGGBIRD
+
+temp1 = blocked flag for flying eggbird (cannot change xdir to chase Keen
+        while this is non-zero)
+
+=============================================================================
+*/
+
+statetype s_egg      = {EGGSPR,      EGGSPR,      think, false, true,      8, 0, 0, NULL, C_Egg, R_Draw, NULL};
+statetype s_eggbroke = {EGGBROKESPR, EGGBROKESPR, step,  false, false, 30000, 0, 0, NULL, NULL, R_Draw, NULL};
+statetype s_eggchip1 = {EGGCHIP1SPR, EGGCHIP1SPR, think, false, false,     0, 0, 0, T_Projectile, NULL, R_Chip, NULL};
+statetype s_eggchip2 = {EGGCHIP2SPR, EGGCHIP2SPR, think, false, false,     0, 0, 0, T_Projectile, NULL, R_Chip, NULL};
+statetype s_eggchip3 = {EGGCHIP3SPR, EGGCHIP3SPR, think, false, false,     0, 0, 0, T_Projectile, NULL, R_Chip, NULL};
+
+statetype s_eggbirdpause = {BIRDWALKL1SPR, BIRDWALKR1SPR, step,       false, true,  120, 128, 0, NULL, C_EggbirdStun, R_Eggbird, &s_eggbirdwalk2};
+statetype s_eggbirdwalk1 = {BIRDWALKL1SPR, BIRDWALKR1SPR, step,       false, true,    7, 128, 0, NULL, C_Eggbird, R_Eggbird, &s_eggbirdwalk2};
+statetype s_eggbirdwalk2 = {BIRDWALKL2SPR, BIRDWALKR2SPR, step,       false, true,    7, 128, 0, NULL, C_Eggbird, R_Eggbird, &s_eggbirdwalk3};
+statetype s_eggbirdwalk3 = {BIRDWALKL3SPR, BIRDWALKR3SPR, step,       false, true,    7, 128, 0, NULL, C_Eggbird, R_Eggbird, &s_eggbirdwalk4};
+statetype s_eggbirdwalk4 = {BIRDWALKL4SPR, BIRDWALKR4SPR, step,       false, true,    7, 128, 0, T_Eggbird, C_Eggbird, R_Eggbird, &s_eggbirdwalk1};
+statetype s_eggbirdfly1  = {BIRDFLY1SPR,   BIRDFLY1SPR,   slidethink, false, false,   8,   0, 0, T_EggbirdFly, C_Eggbird, R_Eggbirdfly, &s_eggbirdfly2};
+statetype s_eggbirdfly2  = {BIRDFLY2SPR,   BIRDFLY2SPR,   slidethink, false, false,   8,   0, 0, T_EggbirdFly, C_Eggbird, R_Eggbirdfly, &s_eggbirdfly3};
+statetype s_eggbirdfly3  = {BIRDFLY3SPR,   BIRDFLY3SPR,   slidethink, false, false,   8,   0, 0, T_EggbirdFly, C_Eggbird, R_Eggbirdfly, &s_eggbirdfly4};
+statetype s_eggbirdfly4  = {BIRDFLY4SPR,   BIRDFLY4SPR,   slidethink, false, false,   8,   0, 0, T_EggbirdFly, C_Eggbird, R_Eggbirdfly, &s_eggbirdfly1};
+statetype s_eggbirddrop  = {BIRDFLY4SPR,   BIRDFLY4SPR,   think,      false, false,   8, 128, 0, T_WeakProjectile, C_Eggbird, R_EggbirdDrop, NULL};
+statetype s_eggbirdstun  = {BIRDSTUNSPR,   BIRDSTUNSPR,   stepthink,  false, false, 240,   0, 0, T_Projectile, C_EggbirdStun, R_Draw, &s_eggbirdstun2};
+statetype s_eggbirdstun2 = {BIRDWALKL1SPR, BIRDWALKR1SPR, step,       false, true,   20,   0, 0, NULL, C_EggbirdStun, R_Draw, &s_eggbirdstun3};
+statetype s_eggbirdstun3 = {BIRDSTUNSPR,   BIRDSTUNSPR,   step,       false, true,   20,   0, 0, NULL, C_EggbirdStun, R_Draw, &s_eggbirdstun4};
+statetype s_eggbirdstun4 = {BIRDWALKL1SPR, BIRDWALKR1SPR, step,       false, true,   20,   0, 0, NULL, C_EggbirdStun, R_Draw, &s_eggbirdstun5};
+statetype s_eggbirdstun5 = {BIRDSTUNSPR,   BIRDSTUNSPR,   step,       false, true,   20,   0, 0, T_EggUnstun, C_EggbirdStun, R_Draw, &s_eggbirdwalk1};
+
+/*
+===========================
+=
+= SpawnEggbird
+=
+===========================
+*/
+
+void SpawnEggbird(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = eggobj;
+	new->active = ac_yes;
+	new->priority = 2;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y) - 0x71;
+	new->xdir = 1;
+	new->ydir = 1;
+	NewState(new, &s_egg);
+}
+
+/*
+===========================
+=
+= T_EggUnstun
+=
+===========================
+*/
+
+void T_EggUnstun(objtype *ob)
+{
+	ob->obclass = eggbirdobj;
+}
+
+/*
+===========================
+=
+= SpawnEggbirdOut
+=
+===========================
+*/
+
+void SpawnEggbirdOut(Sint16 x, Sint16 y)
+{
+	GetNewObj(true);
+	new->obclass = eggbirdobj;
+	new->active = ac_yes;
+	new->priority = 2;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y) - 0xF1;
+	if (new->x < player->x)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	NewState(new, &s_eggbirdpause);
+}
+
+/*
+===========================
+=
+= C_Egg
+=
+===========================
+*/
+
+void C_Egg(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == stunshotobj || hit->obclass == keenobj)
+	{
+		if (hit->obclass == stunshotobj)
+			ExplodeShot(hit);
+
+		ob->obclass = inertobj;
+		ob->active = ac_removable;
+		ChangeState(ob, &s_eggbroke);
+
+		GetNewObj(true);
+		new->obclass = eggbirdobj;
+		new->active = ac_yes;
+		new->x = ob->x;
+		new->y = ob->y - 8*PIXGLOBAL;
+		if (ob->x < player->x)
+		{
+			new->xdir = 1;
+		}
+		else
+		{
+			new->xdir = -1;
+		}
+		new->ydir = 1;
+		NewState(new, &s_eggbirdpause);
+
+		GetNewObj(true);
+		new->obclass = inertobj;
+		new->active = ac_removable;
+		new->x = ob->x;
+		new->y = ob->y;
+		new->xspeed = -28;
+		new->yspeed = -40;
+		NewState(new, &s_eggchip1);
+
+		GetNewObj(true);
+		new->obclass = inertobj;
+		new->active = ac_removable;
+		new->x = ob->x;
+		new->y = ob->y;
+		new->xspeed = 28;
+		new->yspeed = -40;
+		NewState(new, &s_eggchip2);
+
+		GetNewObj(true);
+		new->obclass = inertobj;
+		new->active = ac_removable;
+		new->x = ob->x;
+		new->y = ob->y;
+		new->xspeed = 0;
+		new->yspeed = -56;
+		NewState(new, &s_eggchip3);
+	}
+}
+
+/*
+===========================
+=
+= T_Eggbird
+=
+===========================
+*/
+
+void T_Eggbird(objtype *ob)
+{
+	if (ob->x < player->x)
+	{
+		ob->xdir = 1;
+	}
+	else
+	{
+		ob->xdir = -1;
+	}
+	if (ob->bottom >= player->bottom + 3*TILEGLOBAL && player->hitnorth
+		&& StatePositionOk(ob, &s_eggbirdfly1))	// BUG: StatePositionOk() only works for normal clipping, not for full clipping
+	{
+		// Note: might be a good idea to set xtry to 0 here
+		ob->state = &s_eggbirdfly1;
+		ob->needtoclip = cl_fullclip;
+		ob->yspeed = -8;
+		ob->temp1 = 0;
+	}
+}
+
+/*
+===========================
+=
+= T_EggbirdFly
+=
+===========================
+*/
+
+void T_EggbirdFly(objtype *ob)
+{
+	if (ob->temp1 == 0)
+	{
+		if (ob->x < player->x)
+		{
+			ob->xdir = 1;
+		}
+		else
+		{
+			ob->xdir = -1;
+		}
+	}
+	AccelerateXv(ob, ob->xdir, 16);
+	if (ob->y < player->y)
+	{
+		AccelerateY(ob, 1, 16);
+	}
+	else
+	{
+		AccelerateY(ob, -1, 16);
+	}
+}
+
+/*
+===========================
+=
+= C_Eggbird
+=
+===========================
+*/
+
+void C_Eggbird(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+	else if (hit->obclass == stunshotobj)
+	{
+		ob->xspeed = 0;
+		ob->needtoclip = cl_midclip;
+		StunObj(ob, hit, &s_eggbirdstun);
+	}
+}
+
+/*
+===========================
+=
+= C_EggbirdStun
+=
+===========================
+*/
+
+void C_EggbirdStun(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == stunshotobj)
+	{
+		ob->xspeed = 0;
+		StunObj(ob, hit, &s_eggbirdstun);
+	}
+}
+
+/*
+===========================
+=
+= R_Eggbird
+=
+===========================
+*/
+
+void R_Eggbird(objtype *ob)
+{
+	if (ob->xdir == 1 && ob->hitwest)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = -1;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	else if (ob->xdir == -1 && ob->hiteast)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = 1;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	if (!ob->hitnorth)
+	{
+		ob->yspeed = -16;
+		ob->needtoclip = cl_fullclip;
+		ChangeState(ob, &s_eggbirdfly1);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+===========================
+=
+= R_EggbirdDrop
+=
+===========================
+*/
+
+void R_EggbirdDrop(objtype *ob)	//never actually used
+{
+	if (ob->hitnorth)
+	{
+		ChangeState(ob, &s_eggbirdwalk1);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+===========================
+=
+= R_Chip
+=
+===========================
+*/
+
+void R_Chip(objtype *ob)
+{
+	if (ob->hitnorth)
+		ob->xspeed = ob->yspeed = 0;
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+===========================
+=
+= R_Eggbirdfly
+=
+===========================
+*/
+
+void R_Eggbirdfly(objtype *ob)
+{
+	statetype *oldstate;
+
+	if ((ob->hitsouth || ob->hitnorth) && !ob->temp1)
+		ob->temp1++;
+
+	if (ob->hiteast && ob->xspeed < 0 || ob->hitwest && ob->xspeed > 0)
+	{
+		ob->xspeed = 0;
+		ob->xdir = -ob->xdir;
+	}
+	if (ob->hitnorth == 1 && player->bottom - ob->bottom < 8*PIXGLOBAL)	// BUG? unsigned comparison!
+	{
+		oldstate = ob->state;
+		ob->needtoclip = cl_midclip;
+		ChangeState(ob, &s_eggbirdwalk1);
+		xtry = 0;
+		ytry = 8*PIXGLOBAL;
+		PushObj(ob);
+		if (!ob->hitnorth)
+		{
+			ob->needtoclip = cl_fullclip;
+			ChangeState(ob, oldstate);
+		}
+		return;	// BUG: sprite isn't updated
+	}
+
+	if (!ob->hitsouth && !ob->hitnorth)
+		ob->temp1 = 0;
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+=============================================================================
+
+						  ARACHNUT
+
+=============================================================================
+*/
+
+statetype s_arach1     = {ARACHNUTWALK1SPR, ARACHNUTWALK4SPR, step, false, true,   6, 128, 0, NULL, C_Arach, R_Walk, &s_arach2};
+statetype s_arach2     = {ARACHNUTWALK2SPR, ARACHNUTWALK3SPR, step, false, true,   6, 128, 0, NULL, C_Arach, R_Walk, &s_arach3};
+statetype s_arach3     = {ARACHNUTWALK3SPR, ARACHNUTWALK2SPR, step, false, true,   6, 128, 0, NULL, C_Arach, R_Walk, &s_arach4};
+statetype s_arach4     = {ARACHNUTWALK4SPR, ARACHNUTWALK1SPR, step, false, true,   6, 128, 0, T_Arach, C_Arach, R_Walk, &s_arach1};
+statetype s_arachstun  = {ARACHNUTSTUNSPR,  ARACHNUTSTUNSPR,  step, false, true, 240,   0, 0, NULL, C_ArachStun, R_Draw, &s_arachstun2};
+statetype s_arachstun2 = {ARACHNUTWALK1SPR, ARACHNUTWALK1SPR, step, false, true,  20,   0, 0, NULL, C_ArachStun, R_Draw, &s_arachstun3};
+statetype s_arachstun3 = {ARACHNUTSTUNSPR,  ARACHNUTSTUNSPR,  step, false, true,  20,   0, 0, NULL, C_ArachStun, R_Draw, &s_arachstun4};
+statetype s_arachstun4 = {ARACHNUTWALK1SPR, ARACHNUTWALK1SPR, step, false, true,  20,   0, 0, NULL, C_ArachStun, R_Draw, &s_arachstun5};
+statetype s_arachstun5 = {ARACHNUTSTUNSPR,  ARACHNUTSTUNSPR,  step, false, true,  20,   0, 0, NULL, C_ArachStun, R_Draw, &s_arach1};
+
+/*
+===========================
+=
+= SpawnArachnut
+=
+===========================
+*/
+
+void SpawnArachnut(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = arachnutobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y) - 0x171;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	NewState(new, &s_arach1);
+}
+
+/*
+===========================
+=
+= T_Arach
+=
+===========================
+*/
+
+void T_Arach(objtype *ob)
+{
+	if (ob->x > player->x)
+	{
+		ob->xdir = -1;
+	}
+	else
+	{
+		ob->xdir = 1;
+	}
+}
+
+/*
+===========================
+=
+= C_Arach
+=
+===========================
+*/
+
+void C_Arach(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == stunshotobj)
+	{
+		StunObj(ob, hit, &s_arachstun);
+	}
+	else if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+}
+
+/*
+===========================
+=
+= C_ArachStun
+=
+===========================
+*/
+
+void C_ArachStun(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == stunshotobj)
+	{
+		StunObj(ob, hit, &s_arachstun);
+	}
+}
+
+/*
+=============================================================================
+
+						  SKYPEST
+
+=============================================================================
+*/
+
+statetype s_pestfly1 = {SKYPESTFLYL1SPR, SKYPESTFLYR1SPR, stepthink, true, false, 5, 0, 0, T_PestFly, C_PestFly, R_Pest, &s_pestfly2};
+statetype s_pestfly2 = {SKYPESTFLYL2SPR, SKYPESTFLYR2SPR, stepthink, true, false, 5, 0, 0, T_PestFly, C_PestFly, R_Pest, &s_pestfly1};
+statetype s_squashedpest = {SKYPESTSQUASHEDSPR, SKYPESTSQUASHEDSPR, think, false, false, 0, 0, 0, NULL, NULL, R_Draw, &s_squashedpest};
+statetype s_pestrest1  = {SKYPESTSIT9SPR, SKYPESTSIT9SPR, step, false, false, 100, 0, 0, NULL, C_Squashable, R_Draw, &s_pestrest2};
+statetype s_pestrest2  = {SKYPESTSIT1SPR, SKYPESTSIT1SPR, step, false, false, 10, 0, 0, NULL, C_Squashable, R_Draw, &s_pestrest3};
+statetype s_pestrest3  = {SKYPESTSIT2SPR, SKYPESTSIT2SPR, step, false, false, 10, 0, 0, NULL, C_Squashable, R_Draw, &s_pestrest4};
+statetype s_pestrest4  = {SKYPESTSIT3SPR, SKYPESTSIT3SPR, step, false, false, 10, 0, 0, NULL, C_Squashable, R_Draw, &s_pestrest5};
+statetype s_pestrest5  = {SKYPESTSIT4SPR, SKYPESTSIT4SPR, step, false, false, 10, 0, 0, NULL, C_Squashable, R_Draw, &s_pestrest6};
+statetype s_pestrest6  = {SKYPESTSIT3SPR, SKYPESTSIT3SPR, step, false, false, 10, 0, 0, NULL, C_Squashable, R_Draw, &s_pestrest7};
+statetype s_pestrest7  = {SKYPESTSIT2SPR, SKYPESTSIT2SPR, step, false, false, 10, 0, 0, NULL, C_Squashable, R_Draw, &s_pestrest8};
+statetype s_pestrest8  = {SKYPESTSIT1SPR, SKYPESTSIT1SPR, step, false, false, 10, 0, 0, NULL, C_Squashable, R_Draw, &s_pestrest9};
+statetype s_pestrest9  = {SKYPESTSIT9SPR, SKYPESTSIT9SPR, step, false, false, 60, 0, 0, NULL, C_Squashable, R_Draw, &s_pestrest10};
+statetype s_pestrest10 = {SKYPESTSIT5SPR, SKYPESTSIT5SPR, step, false, false, 10, 0, 0, NULL, C_Squashable, R_Draw, &s_pestrest11};
+statetype s_pestrest11 = {SKYPESTSIT6SPR, SKYPESTSIT6SPR, step, false, false, 10, 0, 0, NULL, C_Squashable, R_Draw, &s_pestrest12};
+statetype s_pestrest12 = {SKYPESTSIT7SPR, SKYPESTSIT7SPR, step, false, false, 10, 0, 0, NULL, C_Squashable, R_Draw, &s_pestrest13};
+statetype s_pestrest13 = {SKYPESTSIT8SPR, SKYPESTSIT8SPR, step, false, false, 10, 0, 0, NULL, C_Squashable, R_Draw, &s_pestrest14};
+statetype s_pestrest14 = {SKYPESTSIT7SPR, SKYPESTSIT7SPR, step, false, false, 10, 0, 0, NULL, C_Squashable, R_Draw, &s_pestrest15};
+statetype s_pestrest15 = {SKYPESTSIT6SPR, SKYPESTSIT6SPR, step, false, false, 10, 0, 0, NULL, C_Squashable, R_Draw, &s_pestrest16};
+statetype s_pestrest16 = {SKYPESTSIT5SPR, SKYPESTSIT5SPR, step, false, false, 10, 0, 0, NULL, C_Squashable, R_Draw, &s_pestrest17};
+statetype s_pestrest17 = {SKYPESTSIT9SPR, SKYPESTSIT9SPR, step, false, false, 100, 0, 0, T_PestRest, C_Squashable, R_Draw, &s_pestfly1};
+
+/*
+===========================
+=
+= SpawnSkypest
+=
+===========================
+*/
+
+void SpawnSkypest(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = skypestobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y);
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	if (US_RndT() < 0x80)
+	{
+		new->ydir = 1;
+	}
+	else
+	{
+		new->ydir = -1;
+	}
+	NewState(new, &s_pestfly1);
+}
+
+/*
+===========================
+=
+= T_PestFly
+=
+===========================
+*/
+
+void T_PestFly(objtype *ob)
+{
+	// BUG: this might be executed twice during the same frame if the
+	// object's animation/state changed during that frame, causing the
+	// object to move at twice the speed during that frame!
+	// To avoid that, return if xtry is not 0 or ytry is not 0.
+
+	if (US_RndT() < tics)
+		ob->xdir = -ob->xdir;
+
+	if (ob->ydir == -1 && US_RndT() < tics)
+		ob->ydir = 1;
+
+	if (ob->ydir == 1 && US_RndT() < tics*2)
+		ob->ydir = -ob->ydir;
+
+	AccelerateX(ob, ob->xdir, 20);
+	AccelerateY(ob, ob->ydir, 20);
+}
+
+/*
+===========================
+=
+= C_PestFly
+=
+===========================
+*/
+
+void C_PestFly(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+		KillKeen();
+
+	if (hit->obclass == stunshotobj)
+	{
+		if (hit->xdir == 1)
+		{
+			ob->xspeed = 20;
+		}
+		else if (hit->xdir == -1)
+		{
+			ob->xspeed = -20;
+		}
+		else if (hit->ydir == 1)
+		{
+			ob->yspeed = 20;
+		}
+		else if (hit->ydir == -1)
+		{
+			ob->yspeed = -20;
+		}
+		ExplodeShot(hit);
+	}
+}
+
+/*
+===========================
+=
+= C_Squashable
+=
+===========================
+*/
+
+void C_Squashable(objtype *ob, objtype *hit)
+{
+	if (hit->state == &s_keenpogodown || hit->state == &s_keenpogo || hit->state == &s_keenpogo2)
+	{
+		ChangeState(ob, &s_squashedpest);
+		SD_PlaySound(SND_SQUISH);
+		ob->obclass = inertobj;
+	}
+}
+
+/*
+===========================
+=
+= T_PestRest
+=
+===========================
+*/
+
+void T_PestRest(objtype *ob)
+{
+	ob->ydir = -1;
+	ob->yspeed = -16;
+	ytry = -144;
+}
+
+/*
+===========================
+=
+= R_Pest
+=
+===========================
+*/
+
+void R_Pest(objtype *ob)
+{
+	if (ob->hitsouth)
+	{
+		ob->yspeed = 8;
+		ob->ydir = 1;
+	}
+	if (ob->hitnorth && !ob->hiteast && !ob->hitwest)
+	{
+		ob->y += 8*PIXGLOBAL;
+		ChangeState(ob, &s_pestrest1);
+	}
+	if (ob->hitwest)
+	{
+		ob->xspeed = 0;
+		ob->xdir = -1;
+	}
+	if (ob->hiteast)
+	{
+		ob->xspeed = 0;
+		ob->xdir = 1;
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
diff --git a/16/keen456/KEEN4-6/KEEN4/K4_ACT2.C b/16/keen456/KEEN4-6/KEEN4/K4_ACT2.C
new file mode 100755
index 00000000..41b0ad95
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN4/K4_ACT2.C
@@ -0,0 +1,1392 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+/*
+K4_ACT2.C
+=========
+
+Contains the following actor types (in this order):
+
+- Wormouth
+- Thundercloud & Lightning
+- Berkeloid & Fireball
+- Inchworm & Foot (in-level)
+- Bounder
+- Lick
+- Platform
+- Dropping Platform
+
+*/
+
+#include "CK_DEF.H"
+
+/*
+=============================================================================
+
+						  WORMOUTH
+
+=============================================================================
+*/
+
+statetype s_worm      = {WORMOUTHSPR,       WORMOUTHSPR,       slide, true,  true,  4, 16, 0, T_Worm,          NULL,                  R_Walk,    &s_worm};
+statetype s_wormpeek1 = {WORMOUTHPEEKL1SPR, WORMOUTHPEEKL1SPR, step,  false, false, 20,  0, 0, NULL,                   C_Worm,   R_Draw,    &s_wormpeek2};
+statetype s_wormpeek2 = {WORMOUTHPEEKL2SPR, WORMOUTHPEEKL2SPR, step,  false, false,  8,  0, 0, NULL,                   C_Worm,   R_Draw,    &s_wormpeek3};
+statetype s_wormpeek3 = {WORMOUTHPEEKL1SPR, WORMOUTHPEEKL1SPR, step,  false, false, 20,  0, 0, T_WormLookLeft,  C_Worm,   R_Draw,    &s_wormpeek4};
+statetype s_wormpeek4 = {WORMOUTHSPR,       WORMOUTHSPR,       step,  false, false,  8,  0, 0, NULL,                   C_Worm,   R_Draw,    &s_wormpeek5};
+statetype s_wormpeek5 = {WORMOUTHPEEKR1SPR, WORMOUTHPEEKR1SPR, step,  false, false, 20,  0, 0, NULL,                   C_Worm,   R_Draw,    &s_wormpeek6};
+statetype s_wormpeek6 = {WORMOUTHPEEKR2SPR, WORMOUTHPEEKR2SPR, step,  false, false,  8,  0, 0, NULL,                   C_Worm,   R_Draw,    &s_wormpeek7};
+statetype s_wormpeek7 = {WORMOUTHPEEKR1SPR, WORMOUTHPEEKR1SPR, step,  false, false, 20,  0, 0, T_WormLookRight, C_Worm,   R_Draw,    &s_wormpeek8};
+statetype s_wormpeek8 = {WORMOUTHSPR,       WORMOUTHSPR,       step,  false, false,  8,  0, 0, T_WormLook,      NULL,                  R_Draw,    &s_worm};
+statetype s_wormbite1 = {WORMOUTHBITEL1SPR, WORMOUTHBITER1SPR, step,  false, false,  8,  0, 0, NULL,                   C_WormKill, R_Draw,    &s_wormbite2};
+statetype s_wormbite2 = {WORMOUTHBITEL2SPR, WORMOUTHBITER2SPR, step,  false, false,  8,  0, 0, NULL,                   C_WormKill, R_Draw,    &s_wormbite3};
+statetype s_wormbite3 = {WORMOUTHBITEL3SPR, WORMOUTHBITER3SPR, step,  false, false, 16,  0, 0, NULL,                   C_WormKill, R_Draw,    &s_wormbite4};
+statetype s_wormbite4 = {WORMOUTHBITEL2SPR, WORMOUTHBITER2SPR, step,  false, false,  8,  0, 0, NULL,                   C_WormKill, R_Draw,    &s_wormbite5};
+statetype s_wormbite5 = {WORMOUTHBITEL1SPR, WORMOUTHBITER1SPR, step,  false, false,  8,  0, 0, NULL,                   C_WormKill, R_Draw,    &s_worm};
+statetype s_wormstun  = {WORMOUTHSTUNSPR,   WORMOUTHSTUNSPR,   think, false, false, 10,  0, 0, T_Projectile,       NULL,                  R_Stunned, NULL};
+
+/*
+===========================
+=
+= SpawnWormMouth
+=
+===========================
+*/
+
+void SpawnWormMouth(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = wormouthobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y) + 0x8F;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	NewState(new, &s_worm);
+}
+
+/*
+===========================
+=
+= T_WormLookRight
+=
+===========================
+*/
+
+void T_WormLookRight(objtype *ob)
+{
+	if (player->x > ob->x)
+	{
+		ob->xdir = 1;
+		ob->state = &s_worm;
+	}
+}
+
+/*
+===========================
+=
+= T_WormLook
+=
+===========================
+*/
+
+void T_WormLook(objtype *ob)
+{
+	if (player->x > ob->x)
+	{
+		ob->xdir = 1;
+	}
+	else
+	{
+		ob->xdir = -1;
+	}
+}
+
+/*
+===========================
+=
+= T_WormLookLeft
+=
+===========================
+*/
+
+void T_WormLookLeft(objtype *ob)
+{
+	if (player->x < ob->x)
+	{
+		ob->xdir = -1;
+		ob->state = &s_worm;
+	}
+}
+
+/*
+===========================
+=
+= T_Worm
+=
+===========================
+*/
+
+void T_Worm(objtype *ob)
+{
+	Sint16 xdist, ydist;
+
+	xdist = player->x - ob->x;
+	ydist = player->bottom - ob->bottom;
+	if ((xdist < -3*TILEGLOBAL || xdist > 3*TILEGLOBAL) && US_RndT() < 6)
+	{
+		ob->state = &s_wormpeek1;
+	}
+	else if (ydist >= -TILEGLOBAL && ydist <= TILEGLOBAL)
+	{
+		if (ob->xdir == 1 && xdist > 8*PIXGLOBAL && xdist < 24*PIXGLOBAL
+			|| ob->xdir == -1 && xdist < -8*PIXGLOBAL && xdist > -32*PIXGLOBAL)
+		{
+			SD_PlaySound(SND_WORMOUTHATTACK);
+			ob->state = &s_wormbite1;
+		}
+	}
+}
+
+/*
+===========================
+=
+= C_Worm
+=
+===========================
+*/
+
+void C_Worm(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == stunshotobj)
+	{
+		StunObj(ob, hit, &s_wormstun);
+	}
+}
+
+/*
+===========================
+=
+= C_WormKill
+=
+===========================
+*/
+
+void C_WormKill(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		if (!(ob->xdir == 1 && ob->x > hit->x || ob->xdir == -1 && ob->x < hit->x))
+		{
+			KillKeen();
+		}
+		return;
+	}
+	else
+	{
+		C_Worm(ob, hit);
+	}
+}
+
+/*
+=============================================================================
+
+						  THUNDERCLOUD
+
+=============================================================================
+*/
+
+statetype s_cloudsleep   = {CLOUDSPR,       CLOUDSPR,       think,     false, false,  20, 0, 0, NULL,         C_CloudSleep, R_Draw,  NULL};
+statetype s_cloudwake    = {CLOUDACTIVESPR, CLOUDACTIVESPR, step,      false, false, 100, 0, 0, NULL,         NULL,         R_Cloud, &s_cloud};
+statetype s_cloud        = {CLOUDACTIVESPR, CLOUDACTIVESPR, think,     false, false,  20, 0, 0, T_Cloud,      NULL,         R_Cloud, NULL};
+statetype s_cloudalign   = {CLOUDACTIVESPR, CLOUDACTIVESPR, think,     false, false,  20, 0, 0, T_CloudAlign, NULL,         R_Cloud, NULL};
+statetype s_cloudcharge  = {CLOUDACTIVESPR, CLOUDACTIVESPR, stepthink, false, false,  60, 0, 0, T_Velocity,   NULL,         R_Cloud, &s_cloud};
+statetype s_cloudattack1 = {CLOUDCHARGESPR, CLOUDCHARGESPR, step,      false, false,  10, 0, 0, NULL,         NULL,         R_Draw,  &s_cloudattack2};
+statetype s_cloudattack2 = {CLOUDACTIVESPR, CLOUDACTIVESPR, step,      false, false,  10, 0, 0, NULL,         NULL,         R_Draw,  &s_cloudattack3};
+statetype s_cloudattack3 = {CLOUDCHARGESPR, CLOUDCHARGESPR, step,      false, false,  10, 0, 0, NULL,         NULL,         R_Draw,  &s_cloudattack4};
+statetype s_cloudattack4 = {CLOUDACTIVESPR, CLOUDACTIVESPR, step,      false, false,  10, 0, 0, T_CloudShoot, NULL,         R_Draw,  &s_cloudattack5};
+statetype s_cloudattack5 = {CLOUDCHARGESPR, CLOUDCHARGESPR, step,      false, false,  10, 0, 0, NULL,         NULL,         R_Draw,  &s_cloudattack6};
+statetype s_cloudattack6 = {CLOUDACTIVESPR, CLOUDACTIVESPR, step,      false, false,  10, 0, 0, NULL,         NULL,         R_Draw,  &s_cloudattack7};
+statetype s_cloudattack7 = {CLOUDCHARGESPR, CLOUDCHARGESPR, step,      false, false,  10, 0, 0, NULL,         NULL,         R_Draw,  &s_cloudattack8};
+statetype s_cloudattack8 = {CLOUDACTIVESPR, CLOUDACTIVESPR, step,      false, false,  10, 0, 0, NULL,         NULL,         R_Draw,  &s_cloudattack9};
+statetype s_cloudattack9 = {CLOUDCHARGESPR, CLOUDCHARGESPR, step,      false, false,  48, 0, 0, NULL,         NULL,         R_Draw,  &s_cloudcharge};
+
+statetype s_bolt1 = {BOLT1SPR, BOLT1SPR, step, false, false, 8, 0, 0, NULL, C_Lethal, R_Draw, &s_bolt2};
+statetype s_bolt2 = {BOLT2SPR, BOLT2SPR, step, false, false, 8, 0, 0, NULL, C_Lethal, R_Draw, &s_bolt3};
+statetype s_bolt3 = {BOLT1SPR, BOLT1SPR, step, false, false, 8, 0, 0, NULL, C_Lethal, R_Draw, &s_bolt4};
+statetype s_bolt4 = {BOLT2SPR, BOLT2SPR, step, false, false, 8, 0, 0, NULL, C_Lethal, R_Draw, &s_bolt5};
+statetype s_bolt5 = {BOLT1SPR, BOLT1SPR, step, false, false, 8, 0, 0, NULL, C_Lethal, R_Draw, &s_bolt6};
+statetype s_bolt6 = {BOLT2SPR, BOLT2SPR, step, false, false, 8, 0, 0, NULL, C_Lethal, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnCloudster
+=
+===========================
+*/
+
+void SpawnCloudster(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = thundercloudobj;
+	new->active = ac_yes;
+	new->priority = 2;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y);
+	new->ydir = new->xdir = 1;
+	NewState(new, &s_cloudsleep);
+}
+
+/*
+===========================
+=
+= T_Cloud
+=
+===========================
+*/
+
+void T_Cloud(objtype *ob)
+{
+	if (US_RndT() < tics)
+		ob->xdir = ob->x > player->x? -1 : 1;
+
+	AccelerateX(ob, ob->xdir, 10);
+	if (player->bottom < ob->bottom || (Sint16)(player->top - ob->bottom) > 64*PIXGLOBAL)
+		return;
+	if (ob->left < player->right && ob->right > player->left)
+	{
+		ob->state = &s_cloudalign;
+	}
+}
+
+/*
+===========================
+=
+= T_CloudAlign
+=
+===========================
+*/
+
+void T_CloudAlign(objtype *ob)
+{
+	AccelerateX(ob, ob->xdir, 10);
+	if (xtry < 0 && (Sint16)((ob->x & 0x7F) + xtry) <= 0)
+	{
+		xtry = -(ob->x & 0x7F);
+		ob->state = &s_cloudattack1;
+	}
+	if (xtry > 0 && (ob->x & 0x7F) + xtry >= 8*PIXGLOBAL)
+	{
+		xtry = 8*PIXGLOBAL - (ob->x & 0x7F);
+		ob->state = &s_cloudattack1;
+	}
+}
+
+/*
+===========================
+=
+= R_Cloud
+=
+===========================
+*/
+
+void R_Cloud(objtype *ob)
+{
+	if (ob->hitwest)
+	{
+		ob->xspeed = 0;
+		ob->xdir = -1;
+	}
+	else if (ob->hiteast)
+	{
+		ob->xspeed = 0;
+		ob->xdir = 1;
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+===========================
+=
+= T_CloudShoot
+=
+===========================
+*/
+
+void T_CloudShoot(objtype *ob)
+{
+	GetNewObj(true);
+	new->obclass = lightningobj;
+	new->active = ac_removable;
+	new->needtoclip = cl_noclip;
+	new->x = ob->x + TILEGLOBAL;
+	new->y = ob->y + TILEGLOBAL;
+	NewState(new, &s_bolt1);
+	SD_PlaySound(SND_THUNDER);
+}
+
+/*
+===========================
+=
+= C_CloudSleep
+=
+===========================
+*/
+
+void C_CloudSleep(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		ChangeState(ob, &s_cloudwake);
+	}
+}
+
+/*
+=============================================================================
+
+						  BERKELOID
+
+temp1 = float offset, in global units (added to ob->y when drawing the sprite)
+temp2 = float speed, in global units per tic (added to temp1 for every tic)
+
+=============================================================================
+*/
+
+statetype s_berkefloat1  = {BERKEWALKL1SPR,  BERKEWALKR1SPR,  slide, false, true,  6, 8, 0, BerkeThink, C_Berke, BerkeWalkReact, &s_berkefloat2};
+statetype s_berkefloat2  = {BERKEWALKL2SPR,  BERKEWALKR2SPR,  slide, false, true,  6, 8, 0, BerkeThink, C_Berke, BerkeWalkReact, &s_berkefloat3};
+statetype s_berkefloat3  = {BERKEWALKL3SPR,  BERKEWALKR3SPR,  slide, false, true,  6, 8, 0, BerkeThink, C_Berke, BerkeWalkReact, &s_berkefloat4};
+statetype s_berkefloat4  = {BERKEWALKL4SPR,  BERKEWALKR4SPR,  slide, false, true,  6, 8, 0, BerkeThink, C_Berke, BerkeWalkReact, &s_berkefloat1};
+statetype s_berkethrow1  = {BERKETHROWL1SPR, BERKETHROWR1SPR, step,  false, false, 6, 0, 0, SetReactThink, C_Berke, BerkeDrawReact, &s_berkethrow2};
+statetype s_berkethrow2  = {BERKETHROWL1SPR, BERKETHROWR1SPR, step,  false, false, 6, 0, 0, SetReactThink, C_Berke, BerkeDrawReact, &s_berkethrow3};
+statetype s_berkethrow3  = {BERKETHROWL1SPR, BERKETHROWR1SPR, step,  false, false, 6, 0, 0, SetReactThink, C_Berke, BerkeDrawReact, &s_berkethrow4};
+statetype s_berkethrow4  = {BERKETHROWL1SPR, BERKETHROWR1SPR, step,  false, false, 6, 0, 0, SetReactThink, C_Berke, BerkeDrawReact, &s_berkethrow5};
+statetype s_berkethrow5  = {BERKETHROWL1SPR, BERKETHROWR1SPR, step,  false, false, 6, 0, 0, SetReactThink, C_Berke, BerkeDrawReact, &s_berkethrow6};
+statetype s_berkethrow6  = {BERKETHROWL1SPR, BERKETHROWR1SPR, step,  false, false, 6, 0, 0, BerkeThrowThink, C_Berke, BerkeDrawReact, &s_berkethrow7};
+statetype s_berkethrow7  = {BERKETHROWL2SPR, BERKETHROWR2SPR, step,  false, false, 6, 0, 0, SetReactThink, C_Berke, BerkeDrawReact, &s_berkethrow8};
+statetype s_berkethrow8  = {BERKETHROWL2SPR, BERKETHROWR2SPR, step,  false, false, 6, 0, 0, SetReactThink, C_Berke, BerkeDrawReact, &s_berkethrow9};
+statetype s_berkethrow9  = {BERKETHROWL2SPR, BERKETHROWR2SPR, step,  false, false, 6, 0, 0, SetReactThink, C_Berke, BerkeDrawReact, &s_berkethrow10};
+statetype s_berkethrow10 = {BERKETHROWL2SPR, BERKETHROWR2SPR, step,  false, false, 6, 0, 0, SetReactThink, C_Berke, BerkeDrawReact, &s_berkethrow11};
+statetype s_berkethrow11 = {BERKETHROWL2SPR, BERKETHROWR2SPR, step,  false, false, 6, 0, 0, SetReactThink, C_Berke, BerkeDrawReact, &s_berkethrow12};
+statetype s_berkethrow12 = {BERKETHROWL2SPR, BERKETHROWR2SPR, step,  false, false, 6, 0, 0, BerkeThrowDone, C_Berke, BerkeDrawReact, &s_berkefloat1};
+
+statetype s_fire1     = {FIREBALL1SPR, FIREBALL1SPR, stepthink, false, false, 6, 0, 0, T_WeakProjectile, C_Lethal, FireReact, &s_fire2};
+statetype s_fire2     = {FIREBALL2SPR, FIREBALL2SPR, stepthink, false, false, 6, 0, 0, T_WeakProjectile, C_Lethal, FireReact, &s_fire1};
+statetype s_fireland1 = {FIREBALL1SPR, FIREBALL1SPR, step, false, false,  6, 0, 0, NULL, C_Berke, R_Draw, &s_fireland2};
+statetype s_fireland2 = {FIREBALL3SPR, FIREBALL3SPR, step, false, false, 12, 0, 0, NULL, C_Berke, R_Draw, &s_fireland3};
+statetype s_fireland3 = {FIREBALL4SPR, FIREBALL4SPR, step, false, false, 12, 0, 0, NULL, C_Berke, R_Draw, &s_fireland4};
+statetype s_fireland4 = {FIREBALL3SPR, FIREBALL3SPR, step, false, false, 12, 0, 0, NULL, C_Berke, R_Draw, &s_fireland5};
+statetype s_fireland5 = {FIREBALL4SPR, FIREBALL4SPR, step, false, false, 12, 0, 0, NULL, C_Berke, R_Draw, &s_fireland6};
+statetype s_fireland6 = {FIREBALL1SPR, FIREBALL1SPR, step, false, false, 12, 0, 0, NULL, C_Berke, R_Draw, &s_fireland7};
+statetype s_fireland7 = {FIREBALL2SPR, FIREBALL2SPR, step, false, false, 12, 0, 0, NULL, C_Berke, R_Draw, &s_fireland8};
+statetype s_fireland8 = {FIREBALL1SPR, FIREBALL1SPR, step, false, false, 12, 0, 0, NULL, C_Berke, R_Draw, &s_fireland9};
+statetype s_fireland9 = {FIREBALL2SPR, FIREBALL2SPR, step, false, false, 12, 0, 0, NULL, C_Berke, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnBerkeloid
+=
+===========================
+*/
+
+void SpawnBerkeloid(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = berkeloidobj;
+	new->active = ac_yes;
+	new->priority = 2;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y) + -2*TILEGLOBAL;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	new->temp2 = 8;
+	NewState(new, &s_berkefloat1);
+}
+
+
+/*
+===========================
+=
+= BerkeThink
+=
+===========================
+*/
+
+void BerkeThink(objtype *ob)
+{
+	Sint16 xdist, ydist;
+
+	if (US_RndT() < 0x20)
+		ob->xdir = player->x < ob->x? -1 : 1;
+
+	if (US_RndT() < 8)
+	{
+		// BUG: might be about to move off a ledge, causing it to get stuck
+		// after throwing (the throw states don't use BerkeWalkReact)!
+		// To avoid that, set xtry to 0 here.
+
+		ob->state = &s_berkethrow1;
+		// BUG? this doesn't play the attack sound
+	}
+	else if (US_RndT() <= 0x40)
+	{
+		xdist = player->x - ob->x;
+		ydist = player->y - ob->y;
+		if (ydist >= -TILEGLOBAL && ydist <= TILEGLOBAL
+			&& (ob->xdir == 1 && xdist > 0 || ob->xdir == -1 && xdist < 0))
+		{
+			// BUG: might be about to move off a ledge, causing it to get stuck
+			// after throwing (the throw states don't use BerkeWalkReact)!
+			// To avoid that, set xtry to 0 here.
+
+			ob->state = &s_berkethrow1;
+			SD_PlaySound(SND_BERKELOIDATTACK);
+		}
+	}
+}
+
+/*
+===========================
+=
+= BerkeThrowThink
+=
+===========================
+*/
+
+void BerkeThrowThink(objtype *ob)
+{
+	GetNewObj(true);
+	new->active = ac_removable;
+	new->obclass = berkeloidobj;
+	new->y = ob->y + 8*PIXGLOBAL;
+	new->yspeed = -8;
+	if (ob->xdir == 1)
+	{
+		new->xspeed = 48;
+		new->x = ob->x + 32*PIXGLOBAL;
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xspeed = -48;
+		new->x = ob->x - 16*PIXGLOBAL;
+		new->xdir = -1;
+	}
+	NewState(new, &s_fire1);
+	ob->needtoreact = true;
+}
+
+/*
+===========================
+=
+= BerkeThrowDone
+=
+===========================
+*/
+
+void BerkeThrowDone(objtype *ob)
+{
+	ob->nothink = 4;
+	ob->needtoreact = true;
+}
+
+/*
+===========================
+=
+= C_Berke
+=
+===========================
+*/
+
+void C_Berke(objtype *ob, objtype *hit)
+{
+	ob++;			// shut up compiler
+	if (hit->obclass == stunshotobj)
+	{
+		ExplodeShot(hit);
+	}
+	else if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+}
+
+/*
+===========================
+=
+= FireReact
+=
+===========================
+*/
+
+void FireReact(objtype *ob)
+{
+	if (ob->hiteast || ob->hitwest)
+		ob->xspeed = 0;
+
+	if (ob->hitnorth)
+	{
+		SD_PlaySound(SND_FIREBALLLAND);
+		ChangeState(ob, &s_fireland1);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+===========================
+=
+= BerkeDrawReact
+=
+===========================
+*/
+
+void BerkeDrawReact(objtype *ob)
+{
+	//float up & down:
+	ob->temp1 = ob->temp1 + ob->temp2 * tics;
+	if (ob->temp1 > 0)
+	{
+		ob->temp1 = 0;
+		ob->temp2 = -8;
+	}
+	else if (ob->temp1 < -TILEGLOBAL)
+	{
+		ob->temp1 = -TILEGLOBAL;
+		ob->temp2 = 8;
+	}
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y+ob->temp1, ob->shapenum, spritedraw, 0);
+}
+
+/*
+===========================
+=
+= BerkeWalkReact
+=
+===========================
+*/
+
+void BerkeWalkReact(objtype *ob)
+{
+	if (ob->xdir == 1 && ob->hitwest)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = -1;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	else if (ob->xdir == -1 && ob->hiteast)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = 1;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	else if (!ob->hitnorth)
+	{
+		ob->x -= ob->xmove*2;
+		ob->xdir = -ob->xdir;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	BerkeDrawReact(ob);
+}
+
+/*
+=============================================================================
+
+						  INCHWORM & FOOT
+
+temp1 = last lasttimecount (for resetting the touch counter after each frame)
+temp2 = touch counter
+
+=============================================================================
+*/
+
+statetype s_footsmoke1 = {SMOKE1SPR, SMOKE1SPR, step, false, false, 12, 0, 0, NULL, NULL, R_Draw, &s_footsmoke2};
+statetype s_footsmoke2 = {SMOKE2SPR, SMOKE2SPR, step, false, false, 12, 0, 0, NULL, NULL, R_Draw, &s_footsmoke3};
+statetype s_footsmoke3 = {SMOKE3SPR, SMOKE3SPR, step, false, false, 12, 0, 0, NULL, NULL, R_Draw, &s_footsmoke4};
+statetype s_footsmoke4 = {SMOKE4SPR, SMOKE4SPR, step, false, false, 12, 0, 0, NULL, NULL, R_Draw, NULL};
+statetype s_inch1      = {INCHWORML1SPR, INCHWORMR1SPR, step, false, true, 30, 128, 0, InchThink, InchContact, R_Walk, &s_inch2};
+statetype s_inch2      = {INCHWORML2SPR, INCHWORMR2SPR, step, false, true, 30, 128, 0, InchThink, InchContact, R_Walk, &s_inch1};
+statetype s_footchange = { -1,  -1, step, false, false, 48, 0, 0, NULL, NULL, R_Draw, &s_footwait};	//never used!
+statetype s_footwait   = {FOOTSPR, FOOTSPR, think, false, false, 30000, 0, 0, NULL, FootContact, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnInchworm
+=
+===========================
+*/
+
+void SpawnInchworm(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = inchwormobj;
+	new->active = ac_yes;
+	new->priority = 2;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y);
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	NewState(new, &s_inch1);
+	new->ticcount = US_RndT() / 32;
+}
+
+/*
+===========================
+=
+= SpawnFoot
+=
+===========================
+*/
+
+void SpawnFoot(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = footobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y-3);
+	NewState(new, &s_footwait);
+}
+
+/*
+===========================
+=
+= InchThink
+=
+===========================
+*/
+
+void InchThink(objtype *ob)
+{
+	if (ob->x > player->x)
+	{
+		ob->xdir = -1;
+	}
+	else
+	{
+		ob->xdir = 1;
+	}
+}
+
+/*
+===========================
+=
+= InchContact
+=
+===========================
+*/
+
+void InchContact(objtype *ob, objtype *hit)
+{
+	objtype *ob2;
+
+	if (hit->obclass != inchwormobj)
+		return;
+
+	if (ob->temp1 != (Sint16)lasttimecount)
+	{
+		ob->temp1 = (Sint16)lasttimecount;
+		ob->temp2 = 0;
+	}
+
+	if (++ob->temp2 != 11)	//11 instead of 12 since the object can't contact itself
+		return;
+
+	//change current inchworm into a foot:
+	SD_PlaySound(SND_MAKEFOOT);
+	ob->y -= 5*TILEGLOBAL;
+	ob->obclass = footobj;
+	ChangeState(ob, &s_footwait);
+
+	//Note: It would make more sense to remove the remaining inchworm BEFORE
+	//spawning the smoke, just in case there are not enough free spots in the
+	//objarray to spawn the smoke. The game won't crash either way, though.
+
+	//spawn smoke:
+	GetNewObj(true);
+	new->x = ob->x -  8*PIXGLOBAL;
+	new->y = ob->y + 16*PIXGLOBAL;
+	new->priority = 3;
+	NewState(new, &s_footsmoke1);
+
+	GetNewObj(true);
+	new->x = ob->x + 16*PIXGLOBAL;
+	new->y = ob->y + 24*PIXGLOBAL;
+	new->priority = 3;
+	NewState(new, &s_footsmoke1);
+
+	GetNewObj(true);
+	new->x = ob->x + 40*PIXGLOBAL;
+	new->y = ob->y + 16*PIXGLOBAL;
+	new->priority = 3;
+	NewState(new, &s_footsmoke1);
+
+	GetNewObj(true);
+	new->x = ob->x;
+	new->y = ob->y - 8*PIXGLOBAL;
+	new->priority = 3;
+	NewState(new, &s_footsmoke1);
+
+	//remove ALL inchworm from the level:
+	for (ob2 = player->next; ob2; ob2=ob2->next)
+	{
+		if (ob2->obclass == inchwormobj)
+			RemoveObj(ob2);
+	}
+}
+
+/*
+===========================
+=
+= FootContact
+=
+===========================
+*/
+
+void FootContact(objtype *ob, objtype *hit)	//completely useless
+{
+	ob++;			// shut up compiler
+	hit++;			// shut up compiler
+}
+
+/*
+=============================================================================
+
+						  BOUNDER
+
+temp1 = if non-zero, pick a new (random) direction when hitting the ground
+        Makes the Bounder jump straight up at least once after having jumped
+		  left/right (unless Keen is riding the Bounder)
+temp2 = jump counter to make the Bounder jump straight up at least twice
+        after Keen has fallen/jumped off
+
+=============================================================================
+*/
+
+statetype s_bounderup1   = {BOUNDERC1SPR,   BOUNDERC1SPR,   stepthink, false, false, 20, 0, 0, T_Projectile, C_Bounder, R_Bounder, &s_bounderup2};
+statetype s_bounderup2   = {BOUNDERC2SPR,   BOUNDERC2SPR,   stepthink, false, false, 20, 0, 0, T_Projectile, C_Bounder, R_Bounder, &s_bounderup1};
+statetype s_bounderside1 = {BOUNDERL1SPR,   BOUNDERR1SPR,   stepthink, false, false, 20, 0, 0, T_Projectile, C_Bounder, R_Bounder, &s_bounderside2};
+statetype s_bounderside2 = {BOUNDERL2SPR,   BOUNDERR2SPR,   stepthink, false, false, 20, 0, 0, T_Projectile, C_Bounder, R_Bounder, &s_bounderside1};
+statetype s_bounderstun  = {BOUNDERC1SPR,   BOUNDERC1SPR,   think,     false, false,  0, 0, 0, T_Projectile, NULL, R_Stunned, &s_bounderstun2};
+statetype s_bounderstun2 = {BOUNDERSTUNSPR, BOUNDERSTUNSPR, think,     false, false,  0, 0, 0, T_Projectile, NULL, R_Stunned, NULL};
+
+/*
+===========================
+=
+= SpawnBounder
+=
+===========================
+*/
+
+void SpawnBounder(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = bounderobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y) + -8*PIXGLOBAL;
+	new->ydir = 1;
+	new->xdir = 0;
+	NewState(new, &s_bounderup1);
+}
+
+/*
+===========================
+=
+= C_Bounder
+=
+===========================
+*/
+
+void C_Bounder(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == stunshotobj)
+	{
+		//basically StunObj(), but in different order:
+		ob->temp1 = 0;
+		ob->temp2 = 0;
+		ob->temp3 = 0;
+		ob->temp4 = ob->obclass;
+		ExplodeShot(hit);
+		ChangeState(ob, &s_bounderstun);
+		ob->obclass = stunnedobj;
+
+		ob->yspeed -= 32;
+	}
+}
+
+/*
+===========================
+=
+= R_Bounder
+=
+===========================
+*/
+
+void R_Bounder(objtype *ob)
+{
+	Sint16 randnum;
+
+	if (ob->hitsouth)
+		ob->yspeed = 0;
+
+	if (ob->hitnorth)
+	{
+		ob->temp2++;
+		if (OnScreen(ob))
+			SD_PlaySound(SND_BOUNCE2);
+
+		ob->yspeed = -50;
+		if (gamestate.riding == ob)
+		{
+			ob->temp2 = 0;
+			if (player->left < ob->left-4*PIXGLOBAL)
+			{
+				ob->xdir = -1;
+			}
+			else if (player->right > ob->right+4*PIXGLOBAL)
+			{
+				ob->xdir = 1;
+			}
+			else
+			{
+				ob->xdir = 0;
+			}
+			ob->xspeed = ob->xdir * 24;
+		}
+		else if (ob->temp2 <= 2 || ob->temp1 == 0)
+		{
+			ob->temp1 = 1;
+			ob->xdir = ob->xspeed = 0;
+			ChangeState(ob, &s_bounderup1);
+		}
+		else
+		{
+			ob->temp1 = 0;
+			randnum = US_RndT();
+			if (randnum < 100)
+			{
+				ob->xdir = -1;
+			}
+			else if (randnum < 200)
+			{
+				ob->xdir = 1;
+			}
+			else
+			{
+				ob->xdir = 0;
+			}
+			ob->xspeed = ob->xdir * 24;
+		}
+
+		if (ob->xdir)
+		{
+			ChangeState(ob, &s_bounderside1);
+		}
+		else
+		{
+			ChangeState(ob, &s_bounderup1);
+		}
+	}
+
+	if (ob->hiteast || ob->hitwest)
+	{
+		ob->xdir = -ob->xdir;
+		ob->xspeed = -ob->xspeed;
+	}
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+=============================================================================
+
+						  LICK
+
+=============================================================================
+*/
+
+statetype s_lick1     = {LICKMOVEL1SPR,   LICKMOVER1SPR,   step,  false, false, 10, 0, 0, LickJumpThink, LickContact, R_Draw, &s_lick2};
+statetype s_lick2     = {LICKMOVEL2SPR,   LICKMOVER2SPR,   think, false, false,  0, 0, 0, T_Projectile, LickContact, LickAirReact, &s_lick3};
+statetype s_lick3     = {LICKMOVEL3SPR,   LICKMOVER3SPR,   think, false, false,  0, 0, 0, T_Projectile, LickContact, LickAirReact, NULL};
+statetype s_lick4     = {LICKMOVEL4SPR,   LICKMOVER4SPR,   step,  false, false, 10, 0, 0, NULL, LickContact, R_Draw, &s_lick1};
+statetype s_licklick1 = {LICKATTACKL1SPR, LICKATTACKR1SPR, step,  true,  false,  4, 0, 0, NULL, LickKillContact, R_Draw, &s_licklick2};
+statetype s_licklick2 = {LICKATTACKL2SPR, LICKATTACKR2SPR, step,  true,  false,  4, 0, 0, NULL, LickKillContact, R_Draw, &s_licklick3};
+statetype s_licklick3 = {LICKATTACKL3SPR, LICKATTACKR3SPR, step,  true,  false,  4, 0, 0, NULL, LickKillContact, R_Draw, &s_licklick4};
+statetype s_licklick4 = {LICKATTACKL2SPR, LICKATTACKR2SPR, step,  true,  false,  4, 0, 0, NULL, LickKillContact, R_Draw, &s_licklick5};
+statetype s_licklick5 = {LICKATTACKL1SPR, LICKATTACKR1SPR, step,  true,  false,  4, 0, 0, NULL, LickKillContact, R_Draw, &s_licklick6};
+statetype s_licklick6 = {LICKATTACKL2SPR, LICKATTACKR2SPR, step,  true,  false,  4, 0, 0, NULL, LickKillContact, R_Draw, &s_licklick7};
+statetype s_licklick7 = {LICKATTACKL3SPR, LICKATTACKR3SPR, step,  true,  false,  4, 0, 0, NULL, LickKillContact, R_Draw, &s_licklick8};
+statetype s_licklick8 = {LICKATTACKL2SPR, LICKATTACKR2SPR, step,  true,  false,  4, 0, 0, NULL, LickKillContact, R_Draw, &s_lick3};
+statetype s_lickstun  = {LICKSTUNSPR,     LICKSTUNSPR,     think, false, false,  0, 0, 0, T_Projectile, NULL, R_Stunned, &s_lickstun2};
+statetype s_lickstun2 = {LICKSTUNSPR,     LICKSTUNSPR,     think, false, false,  0, 0, 0, T_Projectile, NULL, R_Stunned, NULL};
+
+/*
+===========================
+=
+= SpawnLick
+=
+===========================
+*/
+
+void SpawnLick(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = lickobj;
+	new->active = ac_yes;
+	new->priority = 2;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y);
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	new->nothink = US_RndT() / 64;
+	NewState(new, &s_lick3);
+}
+
+/*
+===========================
+=
+= LickJumpThink
+=
+===========================
+*/
+
+void LickJumpThink(objtype *ob)
+{
+	Sint16 xdist, ydist;
+
+	if (ob->x > player->x)
+	{
+		ob->xdir = -1;
+	}
+	else
+	{
+		ob->xdir = 1;
+	}
+
+	xdist = player->x - ob->x;
+	ydist = player->y - ob->y;
+
+	if (ydist >= -TILEGLOBAL && ydist <= TILEGLOBAL	&& 
+		( ob->xdir == 1 && xdist > -2*PIXGLOBAL && xdist < 24*PIXGLOBAL
+		 || ob->xdir == -1 && xdist < 2*PIXGLOBAL && xdist > -32*PIXGLOBAL ) )
+	{
+		SD_PlaySound(SND_LICKATTACK);
+		ob->state = &s_licklick1;
+	}
+	else if (abs(xdist) > 3*TILEGLOBAL)
+	{
+		ob->xspeed = ob->xdir * 32;
+		ob->yspeed = -32;
+	}
+	else
+	{
+		ob->xspeed = (ob->xdir * 32)/2;
+		ob->yspeed = -16;
+	}
+}
+
+/*
+===========================
+=
+= LickContact
+=
+===========================
+*/
+
+void LickContact(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == stunshotobj)
+	{
+		StunObj(ob, hit, &s_lickstun);
+		ob->yspeed -= 16;
+	}
+}
+
+/*
+===========================
+=
+= LickKillContact
+=
+===========================
+*/
+
+void LickKillContact(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		if (ob->xdir == 1 && player->x > ob->x 
+			|| ob->xdir == -1 && player->x < ob->x)
+		{
+			KillKeen();
+		}
+	}
+	else
+	{
+		LickContact(ob, hit);
+	}
+}
+
+/*
+===========================
+=
+= LickAirReact
+=
+===========================
+*/
+
+void LickAirReact(objtype *ob)
+{
+	if (ob->hitnorth)
+		ChangeState(ob, &s_lick4);
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+=============================================================================
+
+						  PLATFORM
+
+temp2 = additional sprite pointer for thruster sprites
+temp3 = additional sprite pointer for thruster sprites
+
+=============================================================================
+*/
+
+statetype s_platform = {PLATFORMSPR, PLATFORMSPR, think, false, false, 0, 0, 0, T_Platform, NULL, R_Platform, NULL};
+
+/*
+===========================
+=
+= SpawnPlatform
+=
+===========================
+*/
+
+void SpawnPlatform(Sint16 x, Sint16 y, Sint16 dir)
+{
+	GetNewObj(false);
+	new->obclass = platformobj;
+	new->active = ac_allways;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y);
+	switch (dir)
+	{
+	case 0:
+		new->xdir = 0;
+		new->ydir = -1;
+		break;
+	case 1:
+		new->xdir = 1;
+		new->ydir = 0;
+		break;
+	case 2:
+		new->xdir = 0;
+		new->ydir = 1;
+		break;
+	case 3:
+		new->xdir = -1;
+		new->ydir = 0;
+		break;
+	}
+	NewState(new, &s_platform);
+}
+
+/*
+===========================
+=
+= T_Platform
+=
+===========================
+*/
+
+void T_Platform(objtype *ob)
+{
+	Uint16 newpos, newtile;
+
+	xtry = ob->xdir * 12 * tics;
+	ytry = ob->ydir * 12 * tics;
+
+	if (ob->xdir == 1)
+	{
+		newpos = ob->right + xtry;
+		newtile = CONVERT_GLOBAL_TO_TILE(newpos);
+		if (ob->tileright != newtile)
+		{
+			if (*(mapsegs[2]+mapbwidthtable[ob->tiletop]/2+newtile) == 31)
+			{
+				ob->xdir = -1;
+				xtry = xtry - (newpos & 0xFF);
+			}
+		}
+	}
+	else if (ob->xdir == -1)
+	{
+		newpos = ob->left + xtry;
+		newtile = CONVERT_GLOBAL_TO_TILE(newpos);
+		if (ob->tileleft != newtile)
+		{
+			if (*(mapsegs[2]+mapbwidthtable[ob->tiletop]/2+newtile) == 31)
+			{
+				ob->xdir = 1;
+				xtry = xtry + (0x100 - (newpos & 0xFF));
+			}
+		}
+	}
+	else if (ob->ydir == 1)
+	{
+		newpos = ob->bottom + ytry;
+		newtile = CONVERT_GLOBAL_TO_TILE(newpos);
+		if (ob->tilebottom != newtile)
+		{
+			if (*(mapsegs[2]+mapbwidthtable[newtile]/2+ob->tileleft) == 31)
+			{
+				if (*(mapsegs[2]+mapbwidthtable[newtile-2]/2+ob->tileleft) == 31)
+				{
+					ytry = 0;
+					ob->needtoreact = true;
+				}
+				else
+				{
+					ob->ydir = -1;
+					ytry = ytry - (newpos & 0xFF);
+				}
+			}
+		}
+	}
+	else if (ob->ydir == -1)
+	{
+		newpos = ob->top + ytry;
+		newtile = CONVERT_GLOBAL_TO_TILE(newpos);
+		if (ob->tiletop != newtile)
+		{
+			if (*(mapsegs[2]+mapbwidthtable[newtile]/2+ob->tileleft) == 31)
+			{
+				if (*(mapsegs[2]+mapbwidthtable[newtile+2]/2+ob->tileleft) == 31)
+				{
+					ytry = 0;
+					ob->needtoreact = true;
+				}
+				else
+				{
+					ob->ydir = 1;
+					ytry = ytry + (0x100 - (newpos & 0xFF));
+				}
+			}
+		}
+	}
+}
+
+/*
+===========================
+=
+= R_Platform
+=
+===========================
+*/
+
+void R_Platform(objtype *ob)
+{
+	Uint16 frame;
+
+	//place platform sprite:
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+	
+	//place (or remove) thruster sprites:
+	frame = (lasttimecount >> 2) & 1;
+	if (ob->xdir == 1)
+	{
+		RF_PlaceSprite((void**)&ob->temp2, ob->x-1*PIXGLOBAL, ob->y+3*PIXGLOBAL, frame+PLATSIDETHRUST1SPR, spritedraw, 0);
+		if (ob->temp3)
+			RF_RemoveSprite((void**)&ob->temp3);
+	}
+	else if (ob->xdir == -1)
+	{
+		if (ob->temp2)
+			RF_RemoveSprite((void**)&ob->temp2);
+		RF_PlaceSprite((void**)&ob->temp3, ob->x+48*PIXGLOBAL, ob->y+5*PIXGLOBAL, frame+PLATSIDETHRUST1SPR, spritedraw, 1);
+	}
+	else if (ob->ydir == -1)
+	{
+		RF_PlaceSprite((void**)&ob->temp2, ob->x+2*PIXGLOBAL, ob->y+9*PIXGLOBAL, frame+PLATLTHRUST1SPR, spritedraw, 0);
+		RF_PlaceSprite((void**)&ob->temp3, ob->x+46*PIXGLOBAL, ob->y+8*PIXGLOBAL, frame+PLATRTHRUST1SPR, spritedraw, 0);
+	}
+	else if (ob->ydir == 1)
+	{
+		if (frame)
+		{
+			RF_PlaceSprite((void**)&ob->temp2, ob->x+2*PIXGLOBAL, ob->y+9*PIXGLOBAL, frame+PLATLTHRUST1SPR, spritedraw, 0);
+			RF_PlaceSprite((void**)&ob->temp3, ob->x+46*PIXGLOBAL, ob->y+8*PIXGLOBAL, frame+PLATRTHRUST1SPR, spritedraw, 0);
+		}
+		else
+		{
+			if (ob->temp2)
+				RF_RemoveSprite((void**)&ob->temp2);
+			if (ob->temp3)
+				RF_RemoveSprite((void**)&ob->temp3);
+		}
+	}
+}
+
+/*
+=============================================================================
+
+						  DROPPING PLATFORM
+
+temp1 = initial y position
+
+=============================================================================
+*/
+
+statetype s_dropplatsit  = {PLATFORMSPR, PLATFORMSPR, think,      false, false, 0, 0,   0, T_DropPlatSit, NULL, R_Draw, NULL};
+statetype s_dropplatfall = {PLATFORMSPR, PLATFORMSPR, think,      false, false, 0, 0,   0, T_DropPlatFall, NULL, R_Draw, NULL};
+statetype s_dropplatrise = {PLATFORMSPR, PLATFORMSPR, slidethink, false, false, 0, 0, -32, T_DropPlatRise, NULL, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnDropPlat
+=
+===========================
+*/
+
+void SpawnDropPlat(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = platformobj;
+	new->active = ac_allways;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = new->temp1 = CONVERT_TILE_TO_GLOBAL(y);
+	new->xdir = 0;
+	new->ydir = 1;
+	new->needtoclip = cl_noclip;
+	NewState(new, &s_dropplatsit);
+}
+
+/*
+===========================
+=
+= T_DropPlatSit
+=
+===========================
+*/
+
+void T_DropPlatSit(objtype *ob)
+{
+	if (gamestate.riding == ob)
+	{
+		ytry = tics * 16;
+		ob->yspeed = 0;
+		if (ob->y + ytry - ob->temp1 >= 8*PIXGLOBAL)
+			ob->state = &s_dropplatfall;
+	}
+}
+
+/*
+===========================
+=
+= T_DropPlatFall
+=
+===========================
+*/
+
+void T_DropPlatFall(objtype *ob)
+{
+	Uint16 newy, ty;
+
+	DoGravity(ob);
+
+	if (ytry >= 15*PIXGLOBAL)
+		ytry = 15*PIXGLOBAL;
+
+	newy = ob->bottom + ytry;
+	ty = CONVERT_GLOBAL_TO_TILE(newy);
+	if (ob->tilebottom != ty)
+	{
+		if (*(mapsegs[2]+mapbwidthtable[ty]/2+ob->tileleft) == 31)
+		{
+			ytry = 0xFF - (ob->bottom & 0xFF);
+			if (gamestate.riding != ob)
+				ob->state = &s_dropplatrise;
+		}
+	}
+}
+
+/*
+===========================
+=
+= T_DropPlatRise
+=
+===========================
+*/
+
+void T_DropPlatRise(objtype *ob)
+{
+	if (gamestate.riding == ob)
+	{
+		ob->yspeed = 0;
+		ob->state = &s_dropplatfall;
+	}
+	else if (ob->y <= ob->temp1)
+	{
+		ytry = ob->temp1 - ob->y;
+		ob->state = &s_dropplatsit;
+	}
+}
diff --git a/16/keen456/KEEN4-6/KEEN4/K4_ACT3.C b/16/keen456/KEEN4-6/KEEN4/K4_ACT3.C
new file mode 100755
index 00000000..287a66fe
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN4/K4_ACT3.C
@@ -0,0 +1,1317 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+/*
+K4_ACT3.C
+=========
+
+Contains the following actor types (in this order):
+
+- Treasure Eater
+- Mimrock
+- Dopefish
+- Schoolfish
+- Sprite
+- Mine
+- Lindsey
+- Dart Shooter & Dart
+- Wetsuit
+
+*/
+
+#include "CK_DEF.H"
+
+/*
+=============================================================================
+
+						  TREASURE EATER
+
+temp1 = turn counter
+
+=============================================================================
+*/
+
+statetype s_eaterstand1 = {EATERSTAND1SPR, EATERSTAND1SPR, step, false, false, 20, 0, 0, NULL, C_Eater, R_Draw, &s_eaterstand2};
+statetype s_eaterstand2 = {EATERSTAND2SPR, EATERSTAND2SPR, step, false, false, 20, 0, 0, T_EaterJump, C_Eater, R_Draw, NULL};
+statetype s_eatertport1 = {SMOKE1SPR, SMOKE1SPR, step, false, false, 20, 0, 0, NULL, C_Eater, R_Draw, &s_eatertport2};
+statetype s_eatertport2 = {SMOKE2SPR, SMOKE2SPR, step, false, false, 20, 0, 0, NULL, C_Eater, R_Draw, &s_eatertport3};
+statetype s_eatertport3 = {SMOKE3SPR, SMOKE3SPR, step, false, false, 20, 0, 0, NULL, C_Eater, R_Draw, &s_eatertport4};
+statetype s_eatertport4 = {SMOKE4SPR, SMOKE4SPR, step, false, false, 20, 0, 0, T_EaterTeleport, C_Eater, R_Draw, &s_eatertport5};
+statetype s_eatertport5 = {SMOKE4SPR, SMOKE4SPR, step, false, false, 20, 0, 0, NULL, C_Eater, R_Draw, &s_eatertport6};
+statetype s_eatertport6 = {SMOKE3SPR, SMOKE3SPR, step, false, false, 20, 0, 0, NULL, C_Eater, R_Draw, &s_eatertport7};
+statetype s_eatertport7 = {SMOKE2SPR, SMOKE2SPR, step, false, false, 20, 0, 0, NULL, C_Eater, R_Draw, &s_eatertport8};
+statetype s_eatertport8 = {SMOKE1SPR, SMOKE1SPR, step, false, false, 20, 0, 0, NULL, C_Eater, R_Draw, &s_eaterjump1};
+statetype s_eaterjump1  = {EATERJUMPL1SPR, EATERJUMPR1SPR, stepthink, false, false, 6, 0, 0, T_WeakProjectile, C_Eater, R_EaterAir, &s_eaterjump2};
+statetype s_eaterjump2  = {EATERJUMPL2SPR, EATERJUMPR2SPR, stepthink, false, false, 6, 0, 0, T_WeakProjectile, C_Eater, R_EaterAir, &s_eaterjump3};
+statetype s_eaterjump3  = {EATERJUMPL3SPR, EATERJUMPR3SPR, stepthink, false, false, 6, 0, 0, T_WeakProjectile, C_Eater, R_EaterAir, &s_eaterjump4};
+statetype s_eaterjump4  = {EATERJUMPL2SPR, EATERJUMPR2SPR, stepthink, false, false, 6, 0, 0, T_WeakProjectile, C_Eater, R_EaterAir, &s_eaterjump1};
+statetype s_eaterstun   = {EATERJUMPL1SPR, EATERJUMPL1SPR, think, false, false, 0, 0, 0, T_Projectile, 0, R_Stunned, &s_eaterstun2};
+statetype s_eaterstun2  = {EATERSTUNSPR, EATERSTUNSPR, think, false, false, 0, 0, 0, T_Projectile, 0, R_Stunned, NULL};
+
+statetype s_eatenbonus1 = {EATENBONUS1SPR, EATENBONUS1SPR, slide, false, false, 10, 0, 8, NULL, NULL, R_Draw, &s_eatenbonus2};
+statetype s_eatenbonus2 = {EATENBONUS2SPR, EATENBONUS2SPR, slide, false, false, 10, 0, 8, NULL, NULL, R_Draw, &s_eatenbonus3};
+statetype s_eatenbonus3 = {EATENBONUS3SPR, EATENBONUS3SPR, slide, false, false, 10, 0, 8, NULL, NULL, R_Draw, &s_eatenbonus4};
+statetype s_eatenbonus4 = {EATENBONUS4SPR, EATENBONUS4SPR, slide, false, false, 10, 0, 8, NULL, NULL, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnEater
+=
+===========================
+*/
+
+void SpawnEater(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = treasureeaterobj;
+	new->active = ac_yes;
+	new->priority = 3;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y) - 24*PIXGLOBAL;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	NewState(new, &s_eaterstand1);
+}
+
+/*
+===========================
+=
+= T_EaterJump
+=
+===========================
+*/
+
+void T_EaterJump(objtype *ob)
+{
+	objtype *ob2;
+	Uint16 x;
+	Sint16 y;
+	Uint16 far *map;
+	Uint16 intile, rowdiff, width;
+
+	ob->state = &s_eaterjump1;
+
+	//jump straight up if below bonus object:
+	for (ob2 = player->next; ob2; ob2 = ob2->next)
+	{
+		if (ob2->obclass == bonusobj && ob2->active == ac_yes
+			&& ob2->right > ob->left && ob2->left < ob->right
+			&& ob2->bottom < ob->top && ob2->bottom + 3*TILEGLOBAL > ob->top)
+		{
+			ob->xspeed = 0;
+			ob->yspeed = -48;
+			return;
+		}
+	}
+
+	//jump straight up if below bonus tile:
+	map = mapsegs[1] + mapbwidthtable[ob->tiletop-3]/2 + ob->tileleft;
+	width = ob->tileright-ob->tileleft+1;
+	rowdiff = mapwidth-width;
+	for (y=0; y<3; y++, map+=rowdiff)
+	{
+		for (x=0; x<width; x++, map++)
+		{
+			intile = tinf[INTILE+*map];
+			if (intile == INTILE_DROP || intile >= INTILE_BONUS100 && intile <= INTILE_AMMO)
+			{
+				ob->xspeed = 0;
+				ob->yspeed = -48;
+				return;
+			}
+		}
+	}
+
+	//vanish after having checked both directions:
+	if (ob->temp1 >= 2)
+	{
+		// BUG? this doesn't play a sound
+		ob->state = &s_eatertport1;
+		return;
+	}
+
+	//jump in current direction if there is a floor in that direction:
+	map = mapsegs[1] + mapbwidthtable[ob->tilebottom-2]/2 + ob->tilemidx;
+	map += ob->xdir * 4;
+	for (y=0; y<4; y++, map+=mapwidth)
+	{
+		if (tinf[NORTHWALL+*map])
+		{
+			ob->xspeed = ob->xdir * 20;
+			ob->yspeed = -24;
+			return;
+		}
+	}
+
+	//couldn't jump in current direction, so turn around:
+	if (++ob->temp1 == 2)
+	{
+		SD_PlaySound(SND_TREASUREEATERVANISH);
+		ob->state = &s_eatertport1;
+		return;
+	}
+
+	//jump in opposite direction:
+	ob->xdir = -ob->xdir;
+	ob->xspeed = ob->xdir * 20;
+	ob->yspeed = -24;
+}
+
+/*
+===========================
+=
+= T_EaterTeleport
+=
+===========================
+*/
+
+void T_EaterTeleport(objtype *ob)
+{
+	objtype *ob2;
+
+	ob->temp1 = 0;
+	for (ob2=player->next; ob2; ob2=ob2->next)
+	{
+		if (ob2->obclass == bonusobj)
+		{
+			ob->x = ob2->x - 8*PIXGLOBAL;
+			ob->y = ob2->y;
+			NewState(ob, &s_eatertport5);
+			return;
+		}
+	}
+	RemoveObj(ob);
+}
+
+/*
+===========================
+=
+= C_Eater
+=
+===========================
+*/
+
+void C_Eater(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == bonusobj)
+	{
+		//BUG? bonus object might be a key, and eating a key makes a level unwinnable
+		hit->obclass = inertobj;
+		hit->priority = 3;
+		ChangeState(hit, &s_eatenbonus1);
+		SD_PlaySound(SND_EATBONUS);
+	}
+	else if (hit->obclass == stunshotobj)
+	{
+		//basically StunObj(), but in different order:
+		ob->temp1 = 0;
+		ob->temp2 = 0;
+		ob->temp3 = 0;
+		ob->temp4 = ob->obclass;
+		ob->obclass = stunnedobj;
+		ExplodeShot(hit);
+		ChangeState(ob, &s_eaterstun);
+
+		ob->yspeed -= 16;
+	}
+}
+
+/*
+===========================
+=
+= EaterInTile
+=
+===========================
+*/
+
+void EaterInTile(objtype *ob)
+{
+	Uint16 x, y;
+	Uint16 far *map;
+	Uint16 rowdiff, intile;
+
+	map = mapsegs[1] + mapbwidthtable[ob->tiletop]/2 + ob->tileleft;
+	rowdiff = mapwidth-(ob->tileright-ob->tileleft+1);
+	for (y=ob->tiletop; y<=ob->tilebottom; y++, map+=rowdiff)
+	{
+		for (x=ob->tileleft; x<=ob->tileright; x++, map++)
+		{
+			intile = tinf[INTILE + *map] & INTILE_TYPEMASK;
+			if (intile == INTILE_DROP || intile >= INTILE_BONUS100 && intile <= INTILE_AMMO)
+			{
+				RF_MemToMap(&zeromap, 1, x, y, 1, 1);
+				GetNewObj(true);
+				new->obclass = inertobj;
+				new->priority = 3;
+				new->needtoclip = cl_noclip;
+				new->x = CONVERT_TILE_TO_GLOBAL(x);
+				new->y = CONVERT_TILE_TO_GLOBAL(y);
+				new->active = ac_removable;
+				ChangeState(new, &s_eatenbonus1);	//using ChangeState and not NewState is fine for noclipping objects
+				//BUG? this doesn't play a sound
+				break;
+			}
+		}
+	}
+}
+
+/*
+===========================
+=
+= R_EaterAir
+=
+===========================
+*/
+
+void R_EaterAir(objtype *ob)
+{
+	EaterInTile(ob);
+
+	if (ob->hitnorth)
+		ChangeState(ob, &s_eaterstand1);
+
+	if (ob->hiteast || ob->hitwest)
+	{
+		ob->temp1++;
+		ob->xdir = -ob->xdir;
+		ob->xspeed = 0;
+	}
+
+	if (ob->hitnorth)	//BUG? maybe this was supposed to check hitsouth as well?
+		ob->yspeed = 0;
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+=============================================================================
+
+						  MIMROCK
+
+=============================================================================
+*/
+
+statetype s_mimrock   = {MIMROCKSPR, MIMROCKSPR, step, false, true, 20, 0, 0, T_MimrockWait, NULL, R_Walk, &s_mimrock};
+statetype s_mimsneak1 = {MIMROCKWALKR1SPR, MIMROCKWALKL1SPR, step, false, true, 6, 64, 0, T_MimrockSneak, C_Mimrock, R_Walk, &s_mimsneak2};
+statetype s_mimsneak2 = {MIMROCKWALKR2SPR, MIMROCKWALKL2SPR, step, false, true, 6, 64, 0, T_MimrockSneak, C_Mimrock, R_Walk, &s_mimsneak3};
+statetype s_mimsneak3 = {MIMROCKWALKR3SPR, MIMROCKWALKL3SPR, step, false, true, 6, 64, 0, T_MimrockSneak, C_Mimrock, R_Walk, &s_mimsneak4};
+statetype s_mimsneak4 = {MIMROCKWALKR4SPR, MIMROCKWALKL4SPR, step, false, true, 6, 64, 0, T_MimrockSneak, C_Mimrock, R_Walk, &s_mimsneak5};
+statetype s_mimsneak5 = {MIMROCKWALKR1SPR, MIMROCKWALKL1SPR, step, false, true, 6, 64, 0, T_MimrockSneak, C_Mimrock, R_Walk, &s_mimsneak6};
+statetype s_mimsneak6 = {MIMROCKWALKR2SPR, MIMROCKWALKL2SPR, step, false, true, 6, 64, 0, T_MimrockSneak, C_Mimrock, R_Walk, &s_mimrock};
+statetype s_mimbonk1  = {MIMROCKJUMPL1SPR, MIMROCKJUMPR1SPR, stepthink, false, false, 24, 0, 0, T_WeakProjectile, C_MimLethal, R_MimAir, &s_mimbonk2};
+statetype s_mimbonk2  = {MIMROCKJUMPL2SPR, MIMROCKJUMPR2SPR, stepthink, false, false, 10, 0, 0, T_WeakProjectile, C_MimLethal, R_MimAir, &s_mimbonk3};
+statetype s_mimbonk3  = {MIMROCKJUMPL3SPR, MIMROCKJUMPR3SPR, think, false, false, 10, 0, 0, T_WeakProjectile, C_MimLethal, R_MimAir, &s_mimbonk2};
+statetype s_mimbounce = {MIMROCKJUMPL3SPR, MIMROCKJUMPR3SPR, think, false, false, 10, 0, 0, T_Projectile, C_Mimrock, R_MimBounce, NULL};
+statetype s_mimstun   = {MIMROCKJUMPL3SPR, MIMROCKJUMPL3SPR, think, false, false, 12, 0, 0, T_Projectile, NULL, R_Stunned, &s_mimstun2};
+statetype s_mimstun2  = {MINROCKSTUNSPR, MINROCKSTUNSPR, think, false, false, 12, 0, 0, T_Projectile, NULL, R_Stunned, NULL};
+
+/*
+===========================
+=
+= SpawnMimrock
+=
+===========================
+*/
+
+void SpawnMimrock(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = mimrockobj;
+	new->active = ac_yes;
+	new->priority = 3;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y)+ -13*PIXGLOBAL;
+	new->ydir = new->xdir = 1;
+	NewState(new, &s_mimrock);
+}
+
+/*
+===========================
+=
+= T_MimrockWait
+=
+===========================
+*/
+
+void T_MimrockWait(objtype *ob)
+{
+	if (abs(ob->bottom - player->bottom) > 5*TILEGLOBAL)
+		return;
+
+	if (abs(ob->x - player->x) > 3*TILEGLOBAL)
+	{
+		if (player->x < ob->x)
+		{
+			if (player->xdir == -1)
+			{
+				ob->xdir = -1;
+				ob->state = &s_mimsneak1;
+			}
+		}
+		else
+		{
+			if (player->xdir == 1)
+			{
+				ob->xdir = 1;
+				ob->state = &s_mimsneak1;
+			}
+		}
+	}
+}
+
+/*
+===========================
+=
+= T_MimrockSneak
+=
+===========================
+*/
+
+void T_MimrockSneak(objtype *ob)
+{
+	if (abs(ob->bottom - player->bottom) > 5*TILEGLOBAL
+		|| ob->xdir != player->xdir)
+	{
+		ob->state = &s_mimrock;
+	}
+	else if (abs(ob->x - player->x) < 4*TILEGLOBAL)
+	{
+		ob->xspeed = ob->xdir * 20;
+		ob->yspeed = -40;
+		ytry = ob->yspeed * tics;
+		ob->state = &s_mimbonk1;
+	}
+}
+
+/*
+===========================
+=
+= C_Mimrock
+=
+===========================
+*/
+
+void C_Mimrock(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == stunshotobj)
+	{
+		//basically StunObj(), but in different order:
+		ob->temp1 = 0;
+		ob->temp2 = 0;
+		ob->temp3 = 0;
+		ob->temp4 = ob->obclass;
+		ob->obclass = stunnedobj;
+		ExplodeShot(hit);
+		ChangeState(ob, &s_mimstun);
+
+		ob->yspeed -= 16;
+	}
+}
+
+/*
+===========================
+=
+= C_MimLethal
+=
+===========================
+*/
+
+void C_MimLethal(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+	else
+	{
+		C_Mimrock(ob, hit);
+	}
+}
+
+/*
+===========================
+=
+= R_MimAir
+=
+===========================
+*/
+
+void R_MimAir(objtype *ob)
+{
+	if (ob->hitnorth)
+	{
+		SD_PlaySound(SND_HELMETHIT);
+		ob->yspeed = -20;
+		ChangeState(ob, &s_mimbounce);
+	}
+
+	if (ob->hiteast || ob->hitwest)
+		ob->xspeed = 0;
+
+	if (ob->hitnorth || ob->hitsouth)
+		ob->yspeed = 0;
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+===========================
+=
+= R_MimBounce
+=
+===========================
+*/
+
+void R_MimBounce(objtype *ob)
+{
+	if (ob->hitnorth)
+	{
+		SD_PlaySound(SND_HELMETHIT);
+		ChangeState(ob, &s_mimrock);
+	}
+
+	if (ob->hiteast || ob->hitwest)
+		ob->xspeed = 0;
+
+	if (ob->hitnorth)
+		ob->yspeed = 0;
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+=============================================================================
+
+						  DOPEFISH
+
+temp1 = blocked (cannot change xdir to chase Keen while this is non-zero)
+temp2 = old x position
+temp3 = old y position
+temp4 = pointer to object being eaten
+        (BUG: pointer may be invalid after loading a saved game!)
+
+=============================================================================
+*/
+
+statetype s_dopefish1  = {DOPEFISHSWIML1SPR, DOPEFISHSWIMR1SPR, stepthink, false, false, 20, 0, 0, T_Dope, C_Dope, R_Fish, &s_dopefish2};
+statetype s_dopefish2  = {DOPEFISHSWIML2SPR, DOPEFISHSWIMR2SPR, stepthink, false, false, 20, 0, 0, T_Dope, C_Dope, R_Fish, &s_dopefish1};
+statetype s_dopeattack = {DOPEFISHHUNGRYLSPR, DOPEFISHHUNGRYRSPR, think, false, false, 0, 0, 0, T_DopeHunt, NULL, R_Draw, NULL};
+statetype s_dopeeat    = {DOPEFISHSWIML1SPR, DOPEFISHSWIMR1SPR, step, false, false, 60, 0, 0, NULL, NULL, R_Draw, &s_dopeburp1};
+statetype s_dopeburp1  = {DOPEFISHBURP1SPR, DOPEFISHBURP1SPR, step, false, false, 60, 0, 0, T_Burp, NULL, R_Draw, &s_dopeburp2};
+statetype s_dopeburp2  = {DOPEFISHBURP2SPR, DOPEFISHBURP2SPR, step, false, false, 60, 0, 0, NULL, NULL, R_Draw, &s_dopereturn};
+statetype s_dopereturn = {DOPEFISHSWIML1SPR, DOPEFISHSWIMR1SPR, think, false, false, 0, 0, 0, T_DopeReturn, NULL, R_Draw, &s_dopefish1};
+
+statetype s_dopefood     = {SCHOOLFISHL1SPR, SCHOOLFISHR1SPR, think, false, false, 0, 0, 0, NULL, NULL, R_Draw, NULL};
+statetype s_keendopefood = {SCUBAKEENDEAD1SPR, SCUBAKEENDEAD1SPR, think, false, false, 0, 0, 0, NULL, NULL, R_Draw, &s_keendieslow};
+statetype s_keendieslow  = {-1, -1, step, false, false, 180, 0, 0, T_EatenKeen, NULL, R_Draw, &s_keendieslow};
+
+statetype s_bubble1 = {BIGBUBBLE1SPR, BIGBUBBLE1SPR, think, false, false, 20, 0, 20, T_Bubble, NULL, R_Draw, &s_bubble2};
+statetype s_bubble2 = {BIGBUBBLE2SPR, BIGBUBBLE2SPR, think, false, false, 20, 0, 20, T_Bubble, NULL, R_Draw, &s_bubble3};
+statetype s_bubble3 = {BIGBUBBLE3SPR, BIGBUBBLE3SPR, think, false, false, 20, 0, 20, T_Bubble, NULL, R_Draw, &s_bubble4};
+statetype s_bubble4 = {BIGBUBBLE4SPR, BIGBUBBLE4SPR, think, false, false, 20, 0, 20, T_Bubble, NULL, R_Draw, &s_bubble1};
+
+/*
+===========================
+=
+= SpawnDopefish
+=
+===========================
+*/
+
+void SpawnDopefish(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = dopefishobj;
+	new->active = ac_yes;
+	new->priority = 2;
+	new->needtoclip = cl_fullclip;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y) + -3*TILEGLOBAL;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	NewState(new, &s_dopefish1);
+}
+
+/*
+===========================
+=
+= T_EatenKeen
+=
+===========================
+*/
+
+void T_EatenKeen(objtype *ob)
+{
+	ob++;			// shut up compiler
+	playstate = ex_died;
+}
+
+/*
+===========================
+=
+= T_Dope
+=
+===========================
+*/
+
+void T_Dope(objtype *ob)
+{
+	if (ob->temp1 == 0)
+	{
+		if (ob->x < player->x)
+		{
+			ob->xdir = 1;
+		}
+		else
+		{
+			ob->xdir = -1;
+		}
+	}
+	AccelerateXv(ob, ob->xdir, 10);
+
+	if (ob->y < player->y)
+	{
+		AccelerateY(ob, 1, 10);
+	}
+	else
+	{
+		AccelerateY(ob, -1, 10);
+	}
+}
+
+/*
+===========================
+=
+= T_DopeHunt
+=
+===========================
+*/
+
+void T_DopeHunt(objtype *ob)
+{
+	objtype *target;
+	Sint16 xdist, ydist;
+
+	target = (objtype *)(ob->temp4);
+	ydist = target->y - TILEGLOBAL - ob->y;
+	if (ob->xdir == 1)
+	{
+		xdist = target->right + 2*PIXGLOBAL - ob->right;
+	}
+	else
+	{
+		xdist = target->left - 2*PIXGLOBAL - ob->left;
+	}
+
+	if (xdist < 0)
+	{
+		xtry = tics * -32;
+		if (xtry < xdist)
+			xtry = xdist;
+	}
+	else
+	{
+		xtry = tics * 32;
+		if (xtry > xdist)
+			xtry = xdist;
+	}
+
+	if (ydist < 0)
+	{
+		ytry = tics * -32;
+		if (ytry < ydist)
+			ytry = ydist;
+	}
+	else
+	{
+		ytry = tics * 32;
+		if (ytry > ydist)
+			ytry = ydist;
+	}
+
+	if (xtry == xdist && ytry == ydist)
+	{
+		if (target == player)
+		{
+			ChangeState(target, &s_keendieslow);
+		}
+		else if (target->state->nextstate)
+		{
+			ChangeState(target, target->state->nextstate);
+		}
+		else
+		{
+			RemoveObj(target);
+		}
+		ob->state = &s_dopeeat;
+	}
+}
+
+/*
+===========================
+=
+= T_DopeReturn
+=
+===========================
+*/
+
+void T_DopeReturn(objtype *ob)
+{
+	Sint16 xdist, ydist;
+
+	ydist = ob->temp3 - ob->y;
+	xdist = ob->temp2 - ob->x;
+
+	if (xdist < 0)
+	{
+		xtry = tics * -32;
+		if (xtry < xdist)
+			xtry = xdist;
+	}
+	else
+	{
+		xtry = tics * 32;
+		if (xtry > xdist)
+			xtry = xdist;
+	}
+
+	if (ydist < 0)
+	{
+		ytry = tics * -32;
+		if (ytry < ydist)
+			ytry = ydist;
+	}
+	else
+	{
+		ytry = tics * 32;
+		if (ytry > ydist)
+			ytry = ydist;
+	}
+
+	if (xtry == xdist && ytry == ydist)
+	{
+		ob->state = ob->state->nextstate;
+		ob->needtoclip = cl_fullclip;
+	}
+}
+
+/*
+===========================
+=
+= T_Burp
+=
+===========================
+*/
+
+void T_Burp(objtype *ob)
+{
+	GetNewObj(true);
+	new->x = ob->x + 56*PIXGLOBAL;
+	new->y = ob->y + 32*PIXGLOBAL;
+	new->obclass = inertobj;
+	new->priority = 3;
+	new->active = ac_removable;
+	new->needtoclip = cl_noclip;
+	new->yspeed = -20;
+	new->xspeed = 4;
+	NewState(new, &s_bubble1);
+	SD_PlaySound(SND_BURP);
+}
+
+/*
+===========================
+=
+= T_Bubble
+=
+===========================
+*/
+
+void T_Bubble(objtype *ob)
+{
+	T_Velocity(ob);
+	if (US_RndT() < tics * 16)
+		ob->xspeed = -ob->xspeed;
+
+	if (ob->y < 3*TILEGLOBAL)
+		RemoveObj(ob);
+}
+
+/*
+===========================
+=
+= C_Dope
+=
+===========================
+*/
+
+void C_Dope(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == schoolfishobj)
+	{
+		ChangeState(hit, &s_dopefood);
+	}
+	else if (hit->obclass == keenobj && !godmode)
+	{
+		hit->obclass = inertobj;	//prevents other objects from killing Keen before he is fully swallowed
+		hit->needtoclip = cl_noclip;
+		SD_PlaySound(SND_KEENDEAD);
+		ChangeState(hit, &s_keendopefood);
+	}
+	else
+	{
+		return;
+	}
+
+	ob->temp2 = ob->x;
+	ob->temp3 = ob->y;
+	ob->temp4 = (Sint16)hit;
+	if (hit->midx < ob->midx)
+	{
+		ob->xdir = -1;
+	}
+	else
+	{
+		ob->xdir = 1;
+	}
+	ChangeState(ob, &s_dopeattack);
+	ob->needtoclip = cl_noclip;
+}
+
+/*
+===========================
+=
+= R_Fish
+=
+===========================
+*/
+
+void R_Fish(objtype *ob)	//for Dopefish and Schoolfish
+{
+	if ((ob->hitsouth || ob->hitnorth) && ob->temp1 == 0)
+		ob->temp1++;
+
+	if (ob->hiteast || ob->hitwest)
+	{
+		ob->xspeed = 0;
+		ob->xdir = -ob->xdir;
+		ob->temp1 = 1;
+	}
+
+	if (!ob->hitsouth && !ob->hitnorth)
+		ob->temp1 = 0;
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+=============================================================================
+
+						  SCHOOLFISH
+
+temp1 = blocked (cannot change xdir to chase Keen while this is non-zero)
+
+=============================================================================
+*/
+
+statetype s_schoolfish1 = {SCHOOLFISHL1SPR, SCHOOLFISHR1SPR, stepthink, false, false, 20, 0, 0, T_SchoolFish, NULL, R_Fish, &s_schoolfish2};
+statetype s_schoolfish2 = {SCHOOLFISHL2SPR, SCHOOLFISHR2SPR, stepthink, false, false, 20, 0, 0, T_SchoolFish, NULL, R_Fish, &s_schoolfish1};
+
+/*
+===========================
+=
+= SpawnSchoolfish
+=
+===========================
+*/
+
+void SpawnSchoolfish(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = schoolfishobj;
+	new->active = ac_yes;
+	new->needtoclip = cl_fullclip;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y);
+	new->ydir = new->xdir = 1;
+	NewState(new, &s_schoolfish1);
+}
+
+/*
+===========================
+=
+= T_SchoolFish
+=
+===========================
+*/
+
+void T_SchoolFish(objtype *ob)
+{
+	if (ob->temp1 == 0)
+	{
+		if (ob->x < player->x)
+		{
+			ob->xdir = 1;
+		}
+		else
+		{
+			ob->xdir = -1;
+		}
+	}
+	AccelerateXv(ob, ob->xdir, 10);
+
+	if (ob->y < player->y)
+	{
+		AccelerateY(ob, 1, 10);
+	}
+	else
+	{
+		AccelerateY(ob, -1, 10);
+	}
+}
+
+/*
+=============================================================================
+
+						  PIXIE (a.k.a. SPRITE)
+
+=============================================================================
+*/
+
+statetype s_pixie       = {SPRITEFLOATSPR,  SPRITEFLOATSPR,  think, false, false, 10, 0, 0, T_Pixie, C_Lethal, R_Draw, &s_pixie};
+statetype s_pixielook   = {SPRITEAIMLSPR,   SPRITEAIMRSPR,   step, false, false, 40, 0, 0, T_PixieCheck, C_Lethal, R_Draw, &s_pixie};
+statetype s_pixieshoot  = {SPRITESHOOTLSPR, SPRITESHOOTRSPR, step, false, false, 40, 0, 0, T_PixieShoot, C_Lethal, R_Draw, &s_pixieshoot2};
+statetype s_pixieshoot2 = {SPRITESHOOTLSPR, SPRITESHOOTRSPR, step, false, false, 30, 0, 0, NULL, C_Lethal, R_Draw, &s_pixie};
+statetype s_pixiefire1  = {SPRITESHOT1SPR,  SPRITESHOT1SPR,  slide, false, false, 10, 64, 0, NULL, C_Lethal, R_Mshot, &s_pixiefire2};
+statetype s_pixiefire2  = {SPRITESHOT2SPR,  SPRITESHOT2SPR,  slide, false, false, 10, 64, 0, NULL, C_Lethal, R_Mshot, &s_pixiefire3};
+statetype s_pixiefire3  = {SPRITESHOT3SPR,  SPRITESHOT3SPR,  slide, false, false, 10, 64, 0, NULL, C_Lethal, R_Mshot, &s_pixiefire4};
+statetype s_pixiefire4  = {SPRITESHOT4SPR,  SPRITESHOT4SPR,  slide, false, false, 10, 64, 0, NULL, C_Lethal, R_Mshot, &s_pixiefire1};
+
+/*
+===========================
+=
+= SpawnPixie
+=
+===========================
+*/
+
+void SpawnPixie(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = pixieobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->needtoclip = cl_noclip;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = new->temp1 = CONVERT_TILE_TO_GLOBAL(y);
+	new->ydir = new->xdir = 1;
+	NewState(new, &s_pixie);
+}
+
+/*
+===========================
+=
+= T_Pixie
+=
+===========================
+*/
+
+void T_Pixie(objtype *ob)
+{
+	AccelerateY(ob, ob->ydir, 8);
+	if ((Sint16)(ob->temp1 - ob->y) > 2*PIXGLOBAL)
+	{
+		ob->ydir = 1;
+	}
+	if ((Sint16)(ob->y - ob->temp1) > 2*PIXGLOBAL)
+	{
+		ob->ydir = -1;
+	}
+
+	if (player->top < ob->bottom && player->bottom > ob->top)
+	{
+		if (player->x < ob->x)
+		{
+			ob->xdir = -1;
+		}
+		else
+		{
+			ob->xdir = 1;
+		}
+		ob->state = &s_pixielook;
+	}
+}
+
+/*
+===========================
+=
+= T_PixieCheck
+=
+===========================
+*/
+
+void T_PixieCheck(objtype *ob)
+{
+	if (player->top < ob->bottom && player->bottom > ob->top)
+		ob->state = &s_pixieshoot;
+}
+
+/*
+===========================
+=
+= T_PixieShoot
+=
+===========================
+*/
+
+void T_PixieShoot(objtype *ob)
+{
+	GetNewObj(true);
+	new->x = ob->x;
+	new->y = ob->y + 8*PIXGLOBAL;
+	new->priority = 0;
+	new->obclass = mshotobj;
+	new->active = ac_removable;
+	SD_PlaySound(SND_KEENFIRE);	//BUG?
+	new->xdir = ob->xdir;
+	NewState(new, &s_pixiefire1);
+	SD_PlaySound(SND_SPRITEFIRE);
+}
+
+/*
+===========================
+=
+= R_Mshot
+=
+===========================
+*/
+
+void R_Mshot(objtype *ob)
+{
+	if (ob->hitnorth || ob->hiteast || ob->hitsouth || ob->hitwest)
+	{
+		RemoveObj(ob);
+	}
+	else
+	{
+		RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+	}
+}
+
+/*
+=============================================================================
+
+						  MINE
+
+=============================================================================
+*/
+statetype s_mine      = {MINESPR,         MINESPR,         think, false, false, 10, 0, 0, T_Platform, C_Mine, R_Draw, &s_mine};
+statetype s_mineboom1 = {MINEEXPLODE1SPR, MINEEXPLODE1SPR, step, false, false, 30, 0, 0, NULL, NULL, R_Draw, &s_mineboom2};
+statetype s_mineboom2 = {MINEEXPLODE2SPR, MINEEXPLODE2SPR, step, false, false, 30, 0, 0, NULL, NULL, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnMine
+=
+===========================
+*/
+
+void SpawnMine(Sint16 x, Sint16 y, Sint16 dir)
+{
+	GetNewObj(false);
+	new->obclass = mineobj;
+	new->active = ac_allways;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y);
+	switch (dir)
+	{
+	case 0:
+		new->xdir = 0;
+		new->ydir = -1;
+		break;
+	case 1:
+		new->xdir = 1;
+		new->ydir = 0;
+		break;
+	case 2:
+		new->xdir = 0;
+		new->ydir = 1;
+		break;
+	case 3:
+		new->xdir = -1;
+		new->ydir = 0;
+		break;
+	}
+	NewState(new, &s_mine);
+}
+
+/*
+===========================
+=
+= C_Mine
+=
+===========================
+*/
+
+void C_Mine(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		ChangeState(ob, &s_mineboom1);
+		SD_PlaySound(SND_MINEEXPLODE);
+		KillKeen();
+	}
+}
+
+/*
+=============================================================================
+
+						  PRINCESS LINDSEY
+
+temp1 = initial y position
+
+=============================================================================
+*/
+statetype s_lindsey1 = {LINDSEY1SPR, LINDSEY1SPR, stepthink, false, false, 20, 0, 0, T_Lindsey, NULL, R_Draw, &s_lindsey2};
+statetype s_lindsey2 = {LINDSEY2SPR, LINDSEY2SPR, stepthink, false, false, 20, 0, 0, T_Lindsey, NULL, R_Draw, &s_lindsey3};
+statetype s_lindsey3 = {LINDSEY3SPR, LINDSEY3SPR, stepthink, false, false, 20, 0, 0, T_Lindsey, NULL, R_Draw, &s_lindsey4};
+statetype s_lindsey4 = {LINDSEY4SPR, LINDSEY4SPR, stepthink, false, false, 20, 0, 0, T_Lindsey, NULL, R_Draw, &s_lindsey1};
+
+/*
+===========================
+=
+= SpawnLindsey
+=
+===========================
+*/
+
+void SpawnLindsey(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = lindseyobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = new->temp1 = CONVERT_TILE_TO_GLOBAL(y) - TILEGLOBAL;
+	new->ydir = 1;
+	NewState(new, &s_lindsey1);
+}
+
+/*
+===========================
+=
+= T_Lindsey
+=
+===========================
+*/
+
+void T_Lindsey(objtype *ob)
+{
+	AccelerateY(ob, ob->ydir, 8);
+	if (ob->temp1 - (Sint16)ob->y > 2*PIXGLOBAL)
+	{
+		ob->ydir = 1;
+	}
+	if ((Sint16)ob->y - ob->temp1 > 2*PIXGLOBAL)
+	{
+		ob->ydir = -1;
+	}
+}
+
+/*
+=============================================================================
+
+						  DARTS
+
+temp1 = direction
+
+=============================================================================
+*/
+
+statetype s_dartthrower = {0, 0, step, false, false, 150, 0, 0, T_DartShoot, NULL, NULL, &s_dartthrower};
+statetype s_dart1       = {DARTL1SPR, DARTR1SPR, slide, false, false, 6, 64, 0, NULL, C_Lethal, R_Mshot, &s_dart2};
+statetype s_dart2       = {DARTL2SPR, DARTR2SPR, slide, false, false, 6, 64, 0, NULL, C_Lethal, R_Mshot, &s_dart1};
+statetype s_dartup1     = {DARTU1SPR, DARTU1SPR, slide, false, false, 6, 0, 64, NULL, C_Lethal, R_Mshot, &s_dartup2};
+statetype s_dartup2     = {DARTU2SPR, DARTU2SPR, slide, false, false, 6, 0, 64, NULL, C_Lethal, R_Mshot, &s_dartup1};
+statetype s_dartdown1   = {DARTD1SPR, DARTD1SPR, slide, false, false, 6, 0, 64, NULL, C_Lethal, R_Mshot, &s_dartdown2};
+statetype s_dartdown2   = {DARTD2SPR, DARTD2SPR, slide, false, false, 6, 0, 64, NULL, C_Lethal, R_Mshot, &s_dartdown1};
+
+/*
+===========================
+=
+= SpawnDartShooter
+=
+===========================
+*/
+
+void SpawnDartShooter(Sint16 x, Sint16 y, Sint16 dir)
+{
+	GetNewObj(false);
+	new->obclass = inertobj;
+	new->active = ac_yes;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->needtoclip = cl_noclip;
+	new->y = CONVERT_TILE_TO_GLOBAL(y);
+	new->temp1 = dir;
+	switch (dir)
+	{
+	case 0:
+		new->y -= 3*PIXGLOBAL;
+		new->x += 9*PIXGLOBAL;
+		new->shapenum = DARTU1SPR;
+		break;
+	case 1:
+		new->x += 8*PIXGLOBAL;
+		new->y += 5*PIXGLOBAL;
+		new->shapenum = DARTR1SPR;
+		break;
+	case 2:
+		new->x += 9*PIXGLOBAL;
+		new->shapenum = DARTD1SPR;
+		break;
+	case 3:
+		new->y += 7*PIXGLOBAL;
+		new->x -= 3*PIXGLOBAL;
+		new->shapenum = DARTL1SPR;
+		break;
+	}
+	NewState(new, &s_dartthrower);
+}
+
+/*
+===========================
+=
+= T_DartShoot
+=
+===========================
+*/
+
+void T_DartShoot(objtype *ob)
+{
+	GetNewObj(true);
+	new->x = ob->x;
+	new->y = ob->y;
+	new->obclass = mshotobj;
+	new->active = ac_removable;
+	switch (ob->temp1)
+	{
+	case 0:
+		new->xdir = 0;
+		new->ydir = -1;
+		NewState(new, &s_dartup1);
+		break;
+	case 1:
+		new->xdir = 1;
+		new->ydir = 0;
+		NewState(new, &s_dart1);
+		break;
+	case 2:
+		new->xdir = 0;
+		new->ydir = 1;
+		NewState(new, &s_dartdown1);
+		break;
+	case 3:
+		new->xdir = -1;
+		new->ydir = 0;
+		NewState(new, &s_dart1);
+		break;
+	}
+	SD_PlaySound(SND_SHOOTDART);
+}
+
+/*
+===========================
+=
+= R_DartThrower
+=
+===========================
+*/
+
+void R_DartThrower(objtype *ob)	//never used
+{
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+=============================================================================
+
+						  SCUBA GEAR
+
+=============================================================================
+*/
+statetype s_scuba = {SCUBASPR, SCUBASPR, step, false, false, 30000, 0, 0, NULL, C_Scuba, R_Draw, &s_scuba};
+
+/*
+===========================
+=
+= SpawnScuba
+=
+===========================
+*/
+
+void SpawnScuba(Sint16 x, Sint16 y)
+{
+	GetNewObj(false);
+	new->obclass = scubaobj;
+	new->active = ac_yes;
+	new->x = CONVERT_TILE_TO_GLOBAL(x);
+	new->y = CONVERT_TILE_TO_GLOBAL(y) + -TILEGLOBAL;
+	NewState(new, &s_scuba);
+}
+
+/*
+===========================
+=
+= C_Scuba
+=
+===========================
+*/
+
+void C_Scuba(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj && hit->hitnorth)
+	{
+		gamestate.wetsuit = true;
+		SD_PlaySound(SND_MAKEFOOT);
+		GotScuba();
+		RF_ForceRefresh();
+		playstate = ex_completed;
+		ob++;			// shut up compiler
+	}
+}
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/KEEN4/K4_DEF.H b/16/keen456/KEEN4-6/KEEN4/K4_DEF.H
new file mode 100755
index 00000000..ee7ced03
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN4/K4_DEF.H
@@ -0,0 +1,511 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+#ifndef __K4_DEF__
+#define __K4_DEF__
+
+/*
+=============================================================================
+
+						GLOBAL CONSTANTS
+
+=============================================================================
+*/
+
+#if GRMODE == CGAGR
+#define MINMEMORY 280000l
+#else
+#define MINMEMORY 310000l
+#endif
+
+#define STARPALETTE   {0, 1, 2, 3, 4, 16, 6, 7, 31, 31, 31, 31, 31, 31, 31, 31, 0}
+#define INTROPALETTE  {0, 24, 24, 7, 1, 1, 1, 1, 17, 17, 17, 17, 19, 19, 19, 19, 0}
+#define SHRINKPALETTE {0, 24, 24, 7, 1, 1, 1, 1, 17, 17, 17, 17, 19, 19, 19, 24, 0}
+
+#define HIGHSCORE_LEFT	24
+#define HIGHSCORE_TOP	51
+#define HIGHSCORE_RIGHT	296
+#define HIGHSCORE_MAP	19
+
+#define STATUS_PRESSKEY_X 160
+
+#define WORLDMAPNAME "Shadowlands"
+#define DROPSNAME "DROPS"
+
+#define STARWARSMUSIC	12
+#define ENDINGMUSIC	7
+
+// levels in this range can NOT be re-entered (BWB level should be > MAXDONELEVEL)
+#define MINDONELEVEL 1
+#define MAXDONELEVEL 17
+
+#define INACTIVATEDIST 4
+
+/*
+=============================================================================
+
+						K4_SPEC DEFINITIONS
+
+=============================================================================
+*/
+
+extern char far swtext[];
+extern char far *levelnames[GAMELEVELS];
+extern char far *levelenter[GAMELEVELS];
+
+void ScanInfoPlane(void);
+void PrincessLindsey(void);
+void RescueJanitor(void);
+void CantSwim(void);
+void GotScuba(void);
+void RescuedMember(void);
+
+extern statetype s_keenswimslow1;
+extern statetype s_keenswimslow2;
+extern statetype s_keenswim1;
+extern statetype s_keenswim2;
+extern statetype s_kbubble1;
+extern statetype s_kbubble2;
+extern statetype s_kbubble3;
+extern statetype s_kbubble4;
+void SpawnSwimKeen(Sint16 x, Sint16 y);
+void SpawnKbubble(objtype *ob);
+void T_KeenSwimSlow(objtype *ob);
+void T_KeenSwim(objtype *ob);
+void C_KeenSwim(objtype *ob, objtype *hit);
+void R_KeenSwim(objtype *ob);
+
+/*
+=============================================================================
+
+						K4_ACT1 DEFINITIONS
+
+=============================================================================
+*/
+
+extern statetype s_miragia0;
+extern statetype s_miragia1;
+extern statetype s_miragia2;
+extern statetype s_miragia3;
+extern statetype s_miragia4;
+extern statetype s_miragia5;
+extern statetype s_miragia6;
+extern statetype s_miragia7;
+void SpawnMiragia(Sint16 x, Sint16 y);
+void T_Miragia0(objtype *ob);
+void T_Miragia1(objtype *ob);
+void T_Miragia2(objtype *ob);
+void T_Miragia3(objtype *ob);
+void T_Miragia4(objtype *ob);
+void T_Miragia5(objtype *ob);
+void T_Miragia6(objtype *ob);
+void T_Miragia7(objtype *ob);
+
+extern statetype s_bonus1;
+extern statetype s_bonus2;
+extern statetype s_bonusrise;
+extern statetype s_splash1;
+extern statetype s_splash2;
+extern statetype s_splash3;
+extern Uint16 bonusshape[];
+void SpawnBonus(Sint16 x, Sint16 y, Sint16 type);
+void SpawnSplash(Sint16 x, Sint16 y);
+void T_Bonus(objtype *ob);
+
+extern statetype s_councilwalk1;
+extern statetype s_councilwalk2;
+extern statetype s_councilstand;
+void SpawnCouncil(Sint16 x, Sint16 y);
+void T_Council(objtype *ob);
+
+extern statetype s_slugwalk1;
+extern statetype s_slugwalk2;
+extern statetype s_slugpiss1;
+extern statetype s_slugstun;
+extern statetype s_slugstunalt;
+extern statetype s_slugslime;
+extern statetype s_slugslime2;
+void SpawnSlug(Sint16 x, Sint16 y);
+void T_Slug(objtype *ob);
+void T_SlugPiss(objtype *ob);
+void C_Slug(objtype *ob, objtype *hit);
+
+extern statetype s_mushroom1;
+extern statetype s_mushroom2;
+void SpawnMadMushroom(Sint16 x, Sint16 y);
+void T_Mushroom(objtype *ob);
+void C_Mushroom(objtype *ob, objtype *hit);
+void R_Mushroom(objtype *ob);
+
+extern statetype s_egg;
+extern statetype s_eggbroke;
+extern statetype s_eggchip1;
+extern statetype s_eggchip2;
+extern statetype s_eggchip3;
+extern statetype s_eggbirdpause;
+extern statetype s_eggbirdwalk1;
+extern statetype s_eggbirdwalk2;
+extern statetype s_eggbirdwalk3;
+extern statetype s_eggbirdwalk4;
+extern statetype s_eggbirdfly1;
+extern statetype s_eggbirdfly2;
+extern statetype s_eggbirdfly3;
+extern statetype s_eggbirdfly4;
+extern statetype s_eggbirddrop;
+extern statetype s_eggbirdstun;
+extern statetype s_eggbirdstun2;
+extern statetype s_eggbirdstun3;
+extern statetype s_eggbirdstun4;
+extern statetype s_eggbirdstun5;
+void SpawnEggbird(Sint16 x, Sint16 y);
+void T_EggUnstun(objtype *ob);
+void SpawnEggbirdOut(Sint16 x, Sint16 y);
+void C_Egg(objtype *ob, objtype *hit);
+void T_Eggbird(objtype *ob);
+void T_EggbirdFly(objtype *ob);
+void C_Eggbird(objtype *ob, objtype *hit);
+void C_EggbirdStun(objtype *ob, objtype *hit);
+void R_Eggbird(objtype *ob);
+void R_EggbirdDrop(objtype *ob);
+void R_Chip(objtype *ob);
+void R_Eggbirdfly(objtype *ob);
+
+extern statetype s_arach1;
+extern statetype s_arach2;
+extern statetype s_arach3;
+extern statetype s_arach4;
+extern statetype s_arachstun;
+extern statetype s_arachstun2;
+extern statetype s_arachstun3;
+extern statetype s_arachstun4;
+extern statetype s_arachstun5;
+void SpawnArachnut(Sint16 x, Sint16 y);
+void T_Arach(objtype *ob);
+void C_Arach(objtype *ob, objtype *hit);
+void C_ArachStun(objtype *ob, objtype *hit);
+
+extern statetype s_pestfly1;
+extern statetype s_pestfly2;
+extern statetype s_squashedpest;
+extern statetype s_pestrest1;
+extern statetype s_pestrest2;
+extern statetype s_pestrest3;
+extern statetype s_pestrest4;
+extern statetype s_pestrest5;
+extern statetype s_pestrest6;
+extern statetype s_pestrest7;
+extern statetype s_pestrest8;
+extern statetype s_pestrest9;
+extern statetype s_pestrest10;
+extern statetype s_pestrest11;
+extern statetype s_pestrest12;
+extern statetype s_pestrest13;
+extern statetype s_pestrest14;
+extern statetype s_pestrest15;
+extern statetype s_pestrest16;
+extern statetype s_pestrest17;
+void SpawnSkypest(Sint16 x, Sint16 y);
+void T_PestFly(objtype *ob);
+void C_PestFly(objtype *ob, objtype *hit);
+void C_Squashable(objtype *ob, objtype *hit);
+void T_PestRest(objtype *ob);
+void R_Pest(objtype *ob);
+
+/*
+=============================================================================
+
+						K4_ACT2 DEFINITIONS
+
+=============================================================================
+*/
+
+extern statetype s_worm;
+extern statetype s_wormpeek1;
+extern statetype s_wormpeek2;
+extern statetype s_wormpeek3;
+extern statetype s_wormpeek4;
+extern statetype s_wormpeek5;
+extern statetype s_wormpeek6;
+extern statetype s_wormpeek7;
+extern statetype s_wormpeek8;
+extern statetype s_wormbite1;
+extern statetype s_wormbite2;
+extern statetype s_wormbite3;
+extern statetype s_wormbite4;
+extern statetype s_wormbite5;
+extern statetype s_wormstun;
+void SpawnWormMouth(Sint16 x, Sint16 y);
+void T_WormLookRight(objtype *ob);
+void T_WormLook(objtype *ob);
+void T_WormLookLeft(objtype *ob);
+void T_Worm(objtype *ob);
+void C_Worm(objtype *ob, objtype *hit);
+void C_WormKill(objtype *ob, objtype *hit);
+
+extern statetype s_cloudsleep;
+extern statetype s_cloudwake;
+extern statetype s_cloud;
+extern statetype s_cloudalign;
+extern statetype s_cloudcharge;
+extern statetype s_cloudattack1;
+extern statetype s_cloudattack2;
+extern statetype s_cloudattack3;
+extern statetype s_cloudattack4;
+extern statetype s_cloudattack5;
+extern statetype s_cloudattack6;
+extern statetype s_cloudattack7;
+extern statetype s_cloudattack8;
+extern statetype s_cloudattack9;
+extern statetype s_bolt1;
+extern statetype s_bolt2;
+extern statetype s_bolt3;
+extern statetype s_bolt4;
+extern statetype s_bolt5;
+extern statetype s_bolt6;
+void SpawnCloudster(Sint16 x, Sint16 y);
+void T_Cloud(objtype *ob);
+void T_CloudAlign(objtype *ob);
+void R_Cloud(objtype *ob);
+void T_CloudShoot(objtype *ob);
+void C_CloudSleep(objtype *ob, objtype *hit);
+
+extern statetype s_berkefloat1;
+extern statetype s_berkefloat2;
+extern statetype s_berkefloat3;
+extern statetype s_berkefloat4;
+extern statetype s_berkethrow1;
+extern statetype s_berkethrow2;
+extern statetype s_berkethrow3;
+extern statetype s_berkethrow4;
+extern statetype s_berkethrow5;
+extern statetype s_berkethrow6;
+extern statetype s_berkethrow7;
+extern statetype s_berkethrow8;
+extern statetype s_berkethrow9;
+extern statetype s_berkethrow10;
+extern statetype s_berkethrow11;
+extern statetype s_berkethrow12;
+extern statetype s_fire1;
+extern statetype s_fire2;
+extern statetype s_fireland1;
+extern statetype s_fireland2;
+extern statetype s_fireland3;
+extern statetype s_fireland4;
+extern statetype s_fireland5;
+extern statetype s_fireland6;
+extern statetype s_fireland7;
+extern statetype s_fireland8;
+extern statetype s_fireland9;
+void SpawnBerkeloid(Sint16 x, Sint16 y);
+void BerkeThink(objtype *ob);
+void BerkeThrowThink(objtype *ob);
+void BerkeThrowDone(objtype *ob);
+void C_Berke(objtype *ob, objtype *hit);
+void FireReact(objtype *ob);
+void BerkeDrawReact(objtype *ob);
+void BerkeWalkReact(objtype *ob);
+
+extern statetype s_footsmoke1;
+extern statetype s_footsmoke2;
+extern statetype s_footsmoke3;
+extern statetype s_footsmoke4;
+extern statetype s_inch1;
+extern statetype s_inch2;
+extern statetype s_footchange;	//never used!
+extern statetype s_footwait;
+void SpawnInchworm(Sint16 x, Sint16 y);
+void SpawnFoot(Sint16 x, Sint16 y);
+void InchThink(objtype *ob);
+void InchContact(objtype *ob, objtype *hit);
+void FootContact(objtype *ob, objtype *hit);
+
+extern statetype s_bounderup1;
+extern statetype s_bounderup2;
+extern statetype s_bounderside1;
+extern statetype s_bounderside2;
+extern statetype s_bounderstun;
+extern statetype s_bounderstun2;
+void SpawnBounder(Sint16 x, Sint16 y);
+void C_Bounder(objtype *ob, objtype *hit);
+void R_Bounder(objtype *ob);
+
+extern statetype s_lick1;
+extern statetype s_lick2;
+extern statetype s_lick3;
+extern statetype s_lick4;
+extern statetype s_licklick1;
+extern statetype s_licklick2;
+extern statetype s_licklick3;
+extern statetype s_licklick4;
+extern statetype s_licklick5;
+extern statetype s_licklick6;
+extern statetype s_licklick7;
+extern statetype s_licklick8;
+extern statetype s_lickstun;
+extern statetype s_lickstun2;
+void SpawnLick(Sint16 x, Sint16 y);
+void LickJumpThink(objtype *ob);
+void LickContact(objtype *ob, objtype *hit);
+void LickKillContact(objtype *ob, objtype *hit);
+void LickAirReact(objtype *ob);
+
+extern statetype s_platform;
+void SpawnPlatform(Sint16 x, Sint16 y, Sint16 dir);
+void T_Platform(objtype *ob);
+void R_Platform(objtype *ob);
+
+extern statetype s_dropplatsit;
+extern statetype s_dropplatfall;
+extern statetype s_dropplatrise;
+void SpawnDropPlat(Sint16 x, Sint16 y);
+void T_DropPlatSit(objtype *ob);
+void T_DropPlatFall(objtype *ob);
+void T_DropPlatRise(objtype *ob);
+
+/*
+=============================================================================
+
+						K4_ACT3 DEFINITIONS
+
+=============================================================================
+*/
+
+extern statetype s_eaterstand1;
+extern statetype s_eaterstand2;
+extern statetype s_eatertport1;
+extern statetype s_eatertport2;
+extern statetype s_eatertport3;
+extern statetype s_eatertport4;
+extern statetype s_eatertport5;
+extern statetype s_eatertport6;
+extern statetype s_eatertport7;
+extern statetype s_eatertport8;
+extern statetype s_eaterjump1;
+extern statetype s_eaterjump2;
+extern statetype s_eaterjump3;
+extern statetype s_eaterjump4;
+extern statetype s_eaterstun;
+extern statetype s_eaterstun2;
+extern statetype s_eatenbonus1;
+extern statetype s_eatenbonus2;
+extern statetype s_eatenbonus3;
+extern statetype s_eatenbonus4;
+void SpawnEater(Sint16 x, Sint16 y);
+void T_EaterJump(objtype *ob);
+void T_EaterTeleport(objtype *ob);
+void C_Eater(objtype *ob, objtype *hit);
+void EaterInTile(objtype *ob);
+void R_EaterAir(objtype *ob);
+
+extern statetype s_mimrock;
+extern statetype s_mimsneak1;
+extern statetype s_mimsneak2;
+extern statetype s_mimsneak3;
+extern statetype s_mimsneak4;
+extern statetype s_mimsneak5;
+extern statetype s_mimsneak6;
+extern statetype s_mimbonk1;
+extern statetype s_mimbonk2;
+extern statetype s_mimbonk3;
+extern statetype s_mimbounce;
+extern statetype s_mimstun;
+extern statetype s_mimstun2;
+void SpawnMimrock(Sint16 x, Sint16 y);
+void T_MimrockWait(objtype *ob);
+void T_MimrockSneak(objtype *ob);
+void C_Mimrock(objtype *ob, objtype *hit);
+void C_MimLethal(objtype *ob, objtype *hit);
+void R_MimAir(objtype *ob);
+void R_MimBounce(objtype *ob);
+
+extern statetype s_dopefish1;
+extern statetype s_dopefish2;
+extern statetype s_dopeattack;
+extern statetype s_dopeeat;
+extern statetype s_dopeburp1;
+extern statetype s_dopeburp2;
+extern statetype s_dopereturn;
+extern statetype s_dopefood;
+extern statetype s_keendopefood;
+extern statetype s_keendieslow;
+extern statetype s_bubble1;
+extern statetype s_bubble2;
+extern statetype s_bubble3;
+extern statetype s_bubble4;
+void SpawnDopefish(Sint16 x, Sint16 y);
+void T_EatenKeen(objtype *ob);
+void T_Dope(objtype *ob);
+void T_DopeHunt(objtype *ob);
+void T_DopeReturn(objtype *ob);
+void T_Burp(objtype *ob);
+void T_Bubble(objtype *ob);
+void C_Dope(objtype *ob, objtype *hit);
+void R_Fish(objtype *ob);
+
+extern statetype s_schoolfish1;
+extern statetype s_schoolfish2;
+void SpawnSchoolfish(Sint16 x, Sint16 y);
+void T_SchoolFish(objtype *ob);
+
+extern statetype s_pixie;
+extern statetype s_pixielook;
+extern statetype s_pixieshoot;
+extern statetype s_pixieshoot2;
+extern statetype s_pixiefire1;
+extern statetype s_pixiefire2;
+extern statetype s_pixiefire3;
+extern statetype s_pixiefire4;
+void SpawnPixie(Sint16 x, Sint16 y);
+void T_Pixie(objtype *ob);
+void T_PixieCheck(objtype *ob);
+void T_PixieShoot(objtype *ob);
+void R_Mshot(objtype *ob);
+
+extern statetype s_mine;
+extern statetype s_mineboom1;
+extern statetype s_mineboom2;
+void SpawnMine(Sint16 x, Sint16 y, Sint16 dir);
+void C_Mine(objtype *ob, objtype *hit);
+
+extern statetype s_lindsey1;
+extern statetype s_lindsey2;
+extern statetype s_lindsey3;
+extern statetype s_lindsey4;
+void SpawnLindsey(Sint16 x, Sint16 y);
+void T_Lindsey(objtype *ob);
+
+extern statetype s_dartthrower;
+extern statetype s_dart1;
+extern statetype s_dart2;
+extern statetype s_dartup1;
+extern statetype s_dartup2;
+extern statetype s_dartdown1;
+extern statetype s_dartdown2;
+void SpawnDartShooter(Sint16 x, Sint16 y, Sint16 dir);
+void T_DartShoot(objtype *ob);
+void R_DartThrower(objtype *ob);
+
+extern statetype s_scuba;
+void SpawnScuba(Sint16 x, Sint16 y);
+void C_Scuba(objtype *ob, objtype *hit);
+
+#endif
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/KEEN4/K4_SPEC.C b/16/keen456/KEEN4-6/KEEN4/K4_SPEC.C
new file mode 100755
index 00000000..45c28615
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN4/K4_SPEC.C
@@ -0,0 +1,1305 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+/*
+K4_SPEC.C
+=========
+
+Contains (in this order):
+
+- lump definition
+- "Star Wars" crawl text
+- level names & messages
+- ScanInfoPlane() - for spawning the level objects and marking required sprites
+- messages for Lindsey, Janitor, Oracle Members and more
+
+- actor states & implementation for swimming Keen
+
+*/
+
+#include "CK_DEF.H"
+
+enum {
+	CONTROLS_LUMP,     //  0
+	KEEN_LUMP,         //  1
+	SUGAR1_LUMP,       //  2
+	SUGAR2_LUMP,       //  3
+	SUGAR3_LUMP,       //  4
+	SUGAR4_LUMP,       //  5
+	SUGAR5_LUMP,       //  6
+	SUGAR6_LUMP,       //  7
+	ONEUP_LUMP,        //  8
+	AMMO_LUMP,         //  9
+	WOLRDKEEN_LUMP,    // 10
+	SLUG_LUMP,         // 11
+	MADMUSHROOM_LUMP,  // 12
+	UNUSED1_LUMP,      // 13
+	LINDSEY_LUMP,      // 14
+	INCHWORM_LUMP,     // 15
+	EATER_LUMP,        // 16
+	COUNCIL_LUMP,      // 17
+	EGGBIRD_LUMP,      // 18
+	MIMROCK_LUMP,      // 19
+	DOPEFISH_LUMP,     // 20
+	SCHOOLFISH_LUMP,   // 21
+	ARACHNUT_LUMP,     // 22
+	SKYPEST_LUMP,      // 23
+	WORMOUTH_LUMP,     // 24
+	LICK_LUMP,         // 25
+	PLATFORM_LUMP,     // 26
+	BOUNDER_LUMP,      // 27
+	THUNDERCLOUD_LUMP, // 28
+	BERKELOID_LUMP,    // 29
+	KEYGEM_LUMP,       // 30
+	DARTS_LUMP,        // 31
+	SCUBAKEEN_LUMP,    // 32
+	SPRITE_LUMP,       // 33
+	MINE_LUMP,         // 34
+	MOON_LUMP,         // 35
+	EGG_LUMP,          // 36
+	NUMLUMPS           // 37
+};
+
+Uint16 lumpstart[NUMLUMPS] = {
+	CONTROLS_LUMP_START,
+	KEEN_LUMP_START,
+	SUGAR1_LUMP_START,
+	SUGAR2_LUMP_START,
+	SUGAR3_LUMP_START,
+	SUGAR4_LUMP_START,
+	SUGAR5_LUMP_START,
+	SUGAR6_LUMP_START,
+	ONEUP_LUMP_START,
+	AMMO_LUMP_START,
+	WORLDKEEN_LUMP_START,
+	SLUG_LUMP_START,
+	MADMUSHROOM_LUMP_START,
+	0,
+	LINDSEY_LUMP_START,
+	INCHWORM_LUMP_START,
+	EATER_LUMP_START,
+	COUNCIL_LUMP_START,
+	EGGBIRD_LUMP_START,
+	MIMROCK_LUMP_START,
+	DOPEFISH_LUMP_START,
+	SCHOOLFISH_LUMP_START,
+	ARACHNUT_LUMP_START,
+	SKYPEST_LUMP_START,
+	WORMOUTH_LUMP_START,
+	LICK_LUMP_START,
+	PLATFORM_LUMP_START,
+	BOUNDER_LUMP_START,
+	THUNDERCLOUD_LUMP_START,
+	BERKELOID_LUMP_START,
+	KEYGEM_LUMP_START,
+	DARTS_LUMP_START,
+	SCUBAKEEN_LUMP_START,
+	SPRITE_LUMP_START,
+	MINE_LUMP_START,
+	MOON_LUMP_START,
+	EGG_LUMP_START
+};
+
+Uint16 lumpend[NUMLUMPS] = {
+	CONTROLS_LUMP_END,
+	KEEN_LUMP_END,
+	SUGAR1_LUMP_END,
+	SUGAR2_LUMP_END,
+	SUGAR3_LUMP_END,
+	SUGAR4_LUMP_END,
+	SUGAR5_LUMP_END,
+	SUGAR6_LUMP_END,
+	ONEUP_LUMP_END,
+	AMMO_LUMP_END,
+	WORLDKEEN_LUMP_END,
+	SLUG_LUMP_END,
+	MADMUSHROOM_LUMP_END,
+	0,
+	LINDSEY_LUMP_END,
+	INCHWORM_LUMP_END,
+	EATER_LUMP_END,
+	COUNCIL_LUMP_END,
+	EGGBIRD_LUMP_END,
+	MIMROCK_LUMP_END,
+	DOPEFISH_LUMP_END,
+	SCHOOLFISH_LUMP_END,
+	ARACHNUT_LUMP_END,
+	SKYPEST_LUMP_END,
+	WORMOUTH_LUMP_END,
+	LICK_LUMP_END,
+	PLATFORM_LUMP_END,
+	BOUNDER_LUMP_END,
+	THUNDERCLOUD_LUMP_END,
+	BERKELOID_LUMP_END,
+	KEYGEM_LUMP_END,
+	DARTS_LUMP_END,
+	SCUBAKEEN_LUMP_END,
+	SPRITE_LUMP_END,
+	MINE_LUMP_END,
+	MOON_LUMP_END,
+	EGG_LUMP_END
+};
+
+boolean lumpneeded[NUMLUMPS];
+
+#if GRMODE == EGAGR
+
+char far swtext[] =
+	"Episode Four\n"
+	"\n"
+	"Secret of the Oracle\n"
+	"\n"
+	"After delivering a\n"
+	"crippling blow to the\n"
+	"plans of Mortimer\n"
+	"McMire and receiving\n"
+	"the praise of the\n"
+	"Vorticon race,\n"
+	"Commander Keen\n"
+	"returned to his home in\n"
+	"the suburbs.\n"
+	"\n"
+	"Here he was forced to\n"
+	"go to bed at an early\n"
+	"hour, and to eat mashed\n"
+	"potatoes.\n"
+	"\n"
+	"Months later, Billy\n"
+	"tinkered around with\n"
+	"his latest invention,\n"
+	"the Photachyon\n"
+	"Transceiver, or faster-\n"
+	"than-light radio. After\n"
+	"picking up a lot of bad\n"
+	"alien sitcoms, he\n"
+	"stumbled upon a strange\n"
+	"message of terrible\n"
+	"importance....\n";
+
+#endif
+
+char far l0n[] = "Shadowlands";
+char far l1n[] = "Border Village";
+char far l2n[] = "Slug Village";
+char far l3n[] = "The Perilous Pit";
+char far l4n[] = "Cave of the Descendents";
+char far l5n[] = "Chasm of Chills";
+char far l6n[] = "Crystalus";
+char far l7n[] = "Hillville";
+char far l8n[] = "Sand Yego";
+char far l9n[] = "Miragia";
+char far l10n[] = "Lifewater Oasis";
+char far l11n[] = "Pyramid of the Moons";
+char far l12n[] = "Pyramid of Shadows";
+char far l13n[] = "Pyramid of the\nGnosticene Ancients";
+char far l14n[] = "Pyramid of the Forbidden";
+char far l15n[] = "Isle of Tar";
+char far l16n[] = "Isle of Fire";
+char far l17n[] = "Well of Wishes";
+char far l18n[] = "Bean-with-Bacon\nMegarocket";
+
+char far l0e[] = "Keen enters the\nShadowlands";
+char far l1e[] = "Keen makes a run for\nthe Border Village";
+char far l2e[] = "Keen slips into\nSlug Village";
+char far l3e[] = "Keen plummets into\nthe The Perilous Pit";	// sic!
+char far l4e[] = "Keen plods down into\nthe Cave of the\nDescendents";
+char far l5e[] = "Keen shivers along\nthe Chasm of Chills";
+char far l6e[] = "Keen reflects upon\nentering Crystalus";
+char far l7e[] = "Keen stumbles upon\nHillville";
+char far l8e[] = "Keen grits his teeth\nand enters Sand Yego";
+char far l9e[] = "Keen disappears into\nMiragia";
+char far l10e[] = "Keen crawls into\nLifewater Oasis";
+char far l11e[] = "Keen backs into the\nPyramid of the Moons";
+char far l12e[] = "Keen move silently in\nthe Pyramid of Shadows";	// sic!
+char far l13e[] = "Keen reverently enters\nthe Pyramid of the\nGnosticene Ancients";
+char far l14e[] = "Keen hesitantly crosses\ninto the Pyramid of the\nForbidden";
+char far l15e[] = "Keen mucks along the\nIsle of Tar";
+char far l16e[] = "Keen blazes across the\nIsle of Fire";
+char far l17e[] = "Keen hopefully enters\nthe Well of Wishes";
+char far l18e[] = "Keen launches into the\nBean-with-Bacon\nMegarocket";
+
+char far *levelnames[GAMELEVELS] = {
+	l0n,
+	l1n,
+	l2n,
+	l3n,
+	l4n,
+	l5n,
+	l6n,
+	l7n,
+	l8n,
+	l9n,
+	l10n,
+	l11n,
+	l12n,
+	l13n,
+	l14n,
+	l15n,
+	l16n,
+	l17n,
+	l18n
+};
+
+char far *levelenter[GAMELEVELS] = {
+	l0e,
+	l1e,
+	l2e,
+	l3e,
+	l4e,
+	l5e,
+	l6e,
+	l7e,
+	l8e,
+	l9e,
+	l10e,
+	l11e,
+	l12e,
+	l13e,
+	l14e,
+	l15e,
+	l16e,
+	l17e,
+	l18e
+};
+
+Uint16 bonuslump[] = {
+	KEYGEM_LUMP, KEYGEM_LUMP, KEYGEM_LUMP, KEYGEM_LUMP,
+	SUGAR1_LUMP, SUGAR2_LUMP, SUGAR3_LUMP,
+	SUGAR4_LUMP, SUGAR5_LUMP, SUGAR6_LUMP,
+	ONEUP_LUMP, AMMO_LUMP
+};
+
+//==========================================================================
+
+/*
+==========================
+=
+= ScanInfoPlane
+=
+= Spawn all actors and mark down special places
+=
+==========================
+*/
+
+void ScanInfoPlane(void)
+{
+	objtype *ob;
+	Uint16 i, x, y, chunk;
+	Sint16 info;
+	Uint16 far *map;
+
+	InitObjArray();                  // start spawning things with a clean slate
+
+	memset(lumpneeded, 0, sizeof(lumpneeded));
+	map = mapsegs[2];
+
+	for (y=0; y<mapheight; y++)
+	{
+		for (x=0; x<mapwidth; x++)
+		{
+			info = *map++;
+
+			if (info == 0)
+				continue;
+
+			switch (info)
+			{
+			case 1:
+				SpawnKeen(x, y, 1);
+				SpawnScore();
+				lumpneeded[KEEN_LUMP] = true;
+				CA_MarkGrChunk(SCOREBOXSPR);
+				break;
+
+			case 2:
+				SpawnKeen(x, y, -1);
+				SpawnScore();
+				lumpneeded[KEEN_LUMP] = true;
+				CA_MarkGrChunk(SCOREBOXSPR);
+				break;
+
+			case 3:
+				SpawnWorldKeen(x, y);
+				SpawnScore();
+				lumpneeded[WOLRDKEEN_LUMP] = true;
+				CA_MarkGrChunk(SCOREBOXSPR);
+				break;
+
+			case 4:
+				SpawnCouncil(x, y);
+				lumpneeded[COUNCIL_LUMP] = true;
+				break;
+
+			case 50:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 49:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 5:
+				SpawnBerkeloid(x, y);
+				lumpneeded[BERKELOID_LUMP] = true;
+				break;
+
+			case 6:
+				SpawnLindsey(x, y);
+				lumpneeded[LINDSEY_LUMP] = true;
+				break;
+
+			case 52:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 51:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 7:
+				SpawnWormMouth(x, y);
+				lumpneeded[WORMOUTH_LUMP] = true;
+				break;
+
+			case 46:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 45:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 8:
+				SpawnSkypest(x, y);
+				lumpneeded[SKYPEST_LUMP] = true;
+				break;
+
+			case 9:
+				SpawnCloudster(x, y);
+				lumpneeded[THUNDERCLOUD_LUMP] = true;
+				break;
+
+			case 10:
+				SpawnFoot(x, y);
+				lumpneeded[INCHWORM_LUMP] = true;	// lump includes the foot sprite
+				// Note: The smoke sprites aren't actually required for the foot!
+				for (i=SMOKE1SPR; i<=SMOKE4SPR; i++)
+				{
+					CA_MarkGrChunk(i);
+				}
+				break;
+
+			case 11:
+				SpawnInchworm(x, y);
+				lumpneeded[INCHWORM_LUMP] = true;
+				for (i=SMOKE1SPR; i<=SMOKE4SPR; i++)
+				{
+					CA_MarkGrChunk(i);
+				}
+				break;
+
+			case 12:
+				SpawnBounder(x, y);
+				lumpneeded[BOUNDER_LUMP] = true;
+				break;
+
+			case 13:
+				SpawnEggbird(x, y);
+				lumpneeded[EGGBIRD_LUMP] = true;
+				lumpneeded[EGG_LUMP] = true;
+				break;
+
+			case 48:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 47:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 14:
+				SpawnLick(x, y);
+				lumpneeded[LICK_LUMP] = true;
+				break;
+
+			case 88:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 87:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 15:
+				SpawnDopefish(x, y);
+				lumpneeded[DOPEFISH_LUMP] = true;
+				break;
+
+			case 16:
+				SpawnSchoolfish(x, y);
+				lumpneeded[SCHOOLFISH_LUMP] = true;
+				break;
+
+			case 24:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 23:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 17:
+				SpawnPixie(x, y);
+				lumpneeded[SPRITE_LUMP] = true;
+				break;
+
+			case 18:
+				SpawnEater(x, y);
+				lumpneeded[EATER_LUMP] = true;
+				break;
+
+			case 19:
+				SpawnMimrock(x, y);
+				lumpneeded[MIMROCK_LUMP] = true;
+				break;
+
+			case 74:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 73:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 20:
+				SpawnArachnut(x, y);
+				lumpneeded[ARACHNUT_LUMP] = true;
+				break;
+
+			case 21:
+				SpawnMadMushroom(x, y);
+				lumpneeded[MADMUSHROOM_LUMP] = true;
+				break;
+
+			case 44:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 43:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 22:
+				SpawnSlug(x, y);
+				lumpneeded[SLUG_LUMP] = true;
+				break;
+
+			case 25:
+				RF_SetScrollBlock(x, y, 1);
+				break;
+
+			case 26:
+				RF_SetScrollBlock(x, y, 0);
+				break;
+
+			case 27:
+			case 28:
+			case 29:
+			case 30:
+				SpawnPlatform(x, y, info-27);
+				lumpneeded[PLATFORM_LUMP] = true;;
+				break;
+
+			case 32:
+				SpawnDropPlat(x, y);
+				lumpneeded[PLATFORM_LUMP] = true;
+				break;
+
+			case 33:
+				SpawnMiragia(x, y);
+				break;
+
+			case 34:
+				if (gamestate.ammo < 5)
+				{
+					SpawnBonus(x, y, 11);
+					lumpneeded[bonuslump[11]] = true;
+				}
+				break;
+
+			case 35:
+				SpawnScuba(x, y);
+				CA_MarkGrChunk(SCUBASPR);
+				break;
+
+			case 42:
+				SpawnSwimKeen(x, y);
+				SpawnScore();
+				lumpneeded[SCUBAKEEN_LUMP] = true;
+				//mark pickup shapes:
+				for (i=BONUS100SPR; i<=BONUSCLIPSPR; i++)
+				{
+					CA_MarkGrChunk(i);
+				}
+				CA_MarkGrChunk(SCOREBOXSPR);
+				break;
+
+			case 83:
+			case 84:
+			case 85:
+			case 86:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+				SpawnDartShooter(x, y, info-83);
+				lumpneeded[DARTS_LUMP] = true;
+				break;
+
+			case 79:
+			case 80:
+			case 81:
+			case 82:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+				SpawnDartShooter(x, y, info-79);
+				lumpneeded[DARTS_LUMP] = true;
+				break;
+
+			case 53:
+			case 54:
+			case 55:
+			case 56:
+				SpawnDartShooter(x, y, info-53);
+				lumpneeded[DARTS_LUMP] = true;
+				break;
+
+			case 57:
+			case 58:
+			case 59:
+			case 60:
+			case 61:
+			case 62:
+			case 63:
+			case 64:
+			case 65:
+			case 66:
+			case 67:
+			case 68:
+				SpawnBonus(x, y, info-57);
+				lumpneeded[bonuslump[info-57]] = true;
+				break;
+
+			case 69:
+			case 70:
+			case 71:
+			case 72:
+				SpawnMine(x, y, info-69);
+				lumpneeded[MINE_LUMP] = true;
+				break;
+
+			case 75:
+				lumpneeded[MOON_LUMP] = true;
+				break;
+
+			case 78:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 77:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 76:
+				SpawnEggbirdOut(x, y);
+				lumpneeded[EGGBIRD_LUMP] = true;
+				break;
+			}
+		}
+	}
+
+	for (ob = player; ob; ob = ob->next)
+	{
+		if (ob->active != ac_allways)
+			ob->active = ac_no;
+	}
+
+	for (i = 0; i < NUMLUMPS; i++)
+	{
+		if (lumpneeded[i])
+		{
+			for (chunk = lumpstart[i]; chunk <= lumpend[i]; chunk++)
+			{
+				CA_MarkGrChunk(chunk);
+			}
+		}
+	}
+}
+
+//============================================================================
+
+/*
+===========================
+=
+= PrincessLindsey
+=
+===========================
+*/
+
+char *lindseytext[2] =
+{
+	"There's gear to help\n"
+	"you swim in Three-Tooth\n"
+	"Lake. It is hidden in\n"
+	"Miragia.\n"
+	,
+	"The way to the Pyramid\n"
+	"of the Forbidden lies\n"
+	"under the Pyramid of\n"
+	"Moons.\n"
+};
+
+char *klindseytext[2] =
+{
+	"Thanks, your Highness!"
+	,
+	"Thanks for the\n"
+	"mysterious clue,\n"
+	"Princess!\n"
+};
+
+void PrincessLindsey(void)
+{
+	SD_WaitSoundDone();
+	StopMusic();
+	CA_UpLevel();
+	CA_MarkGrChunk(LINDSEYPIC);
+	CA_MarkGrChunk(KEENTALK1PIC);
+	CA_MarkGrChunk(KEENTALK2PIC);
+	CA_CacheMarks(NULL);
+	VW_FixRefreshBuffer();
+
+	US_CenterWindow(26, 8);
+	VWB_DrawPic(WindowX, WindowY, LINDSEYPIC);
+	PrintY += 6;
+	WindowW -= 48;
+	WindowX += 48;
+	US_CPrint("Princess Lindsey says:\n");
+	if (mapon == 7)
+	{
+		US_CPrint(lindseytext[0]);
+	}
+	else
+	{
+		US_CPrint(lindseytext[1]);
+	}
+	VW_UpdateScreen();
+	SD_PlaySound(SND_MAKEFOOT);
+	VW_WaitVBL(60);
+	IN_ClearKeysDown();
+	IN_Ack();
+
+	US_CenterWindow(26, 8);
+	VWB_DrawPic(WindowX+WindowW-48, WindowY, KEENTALK1PIC);
+	WindowW -= 48;
+	PrintY += 12;
+	if (mapon == 7)
+	{
+		US_CPrint(klindseytext[0]);
+	}
+	else
+	{
+		US_CPrint(klindseytext[1]);
+	}
+	VW_UpdateScreen();
+	VW_WaitVBL(30);
+	IN_ClearKeysDown();
+	IN_Ack();
+
+	VWB_DrawPic(WindowX+WindowW, WindowY, KEENTALK2PIC);
+	VW_UpdateScreen();
+	VW_WaitVBL(30);
+	IN_ClearKeysDown();
+	IN_Ack();
+
+	CA_DownLevel();
+	StartMusic(gamestate.mapon);
+
+	//reset scorebox (sprite may have been re-cached by CA_DownLevel)
+	scoreobj->temp2 = -1;
+	scoreobj->temp1 = -1;
+	scoreobj->temp3 = -1;
+	scoreobj->temp4 = -1;
+}
+
+//============================================================================
+
+/*
+===========================
+=
+= RescueJanitor
+=
+===========================
+*/
+
+char far jantext1[] =
+	"Thanks for going to all\n"
+	"that trouble, but I'm\n"
+	"just the janitor for the\n"
+	"High Council.";
+
+char far jantext2[] =
+	"I tried to tell the\n"
+	"Shikadi that but they\n"
+	"just wouldn't listen...";
+
+char far keenjantext[] =
+	"This had better\n"
+	"be a joke.";
+
+char far jantext3[] =
+	"Sorry.  You aren't\n"
+	"mad, are you?";
+
+void RescueJanitor(void)
+{
+	char str[200];
+
+	SD_WaitSoundDone();
+	CA_UpLevel();
+	CA_MarkGrChunk(ORACLEPIC);
+	CA_MarkGrChunk(KEENTALK1PIC);
+	CA_MarkGrChunk(KEENMADPIC);
+	CA_CacheMarks(NULL);
+	VW_FixRefreshBuffer();
+	StartMusic(-1);
+	
+	US_CenterWindow(26, 8);
+	VWB_DrawPic(WindowX, WindowY, ORACLEPIC);
+	PrintY += 6;
+	WindowW -= 48;
+	WindowX += 48;
+	_fstrcpy(str, jantext1);
+	US_CPrint(str);
+	VW_UpdateScreen();
+	VW_WaitVBL(60);
+	IN_ClearKeysDown();
+	IN_Ack();
+
+	US_CenterWindow(26, 8);
+	VWB_DrawPic(WindowX, WindowY, ORACLEPIC);
+	PrintY += 6;
+	WindowW -= 48;
+	WindowX += 48;
+	_fstrcpy(str, jantext2);
+	US_CPrint(str);
+	VW_UpdateScreen();
+	VW_WaitVBL(60);
+	IN_ClearKeysDown();
+	IN_Ack();
+
+	US_CenterWindow(26, 8);
+	VWB_DrawPic(WindowX+WindowW-48, WindowY, KEENTALK1PIC);
+	WindowW -= 48;
+	PrintY += 12;
+	_fstrcpy(str, keenjantext);
+	US_CPrint(str);
+	VW_UpdateScreen();
+	VW_WaitVBL(60);
+	IN_ClearKeysDown();
+	IN_Ack();
+
+	US_CenterWindow(26, 8);
+	VWB_DrawPic(WindowX, WindowY, ORACLEPIC);
+	PrintY += 6;
+	WindowW -= 48;
+	WindowX += 48;
+	_fstrcpy(str, jantext3);
+	US_CPrint(str);
+	VW_UpdateScreen();
+	VW_WaitVBL(60);
+	IN_ClearKeysDown();
+	IN_Ack();
+
+	US_CenterWindow(26, 8);
+	VWB_DrawPic(WindowX+WindowW-48, WindowY, KEENTALK1PIC);
+	VWB_DrawPic(WindowX+WindowW-40, WindowY+24, KEENMADPIC);
+	VW_UpdateScreen();
+	VW_WaitVBL(30);
+	IN_ClearKeysDown();
+	IN_Ack();
+
+	StopMusic();
+	CA_DownLevel();
+	StartMusic(gamestate.mapon);
+
+	//BUG: scorebox needs to be reset here (sprite may have been re-cached by CA_DownLevel)
+}
+
+//============================================================================
+
+/*
+===========================
+=
+= CanitSwim
+=
+===========================
+*/
+
+void CantSwim(void)
+{
+	SD_WaitSoundDone();
+	CA_UpLevel();	// kinda useless without CA_CacheMarks or CA_SetGrPurge
+	// BUG: haven't made anything purgable here, caching the pic may cause an "out of memory" crash
+	CA_CacheGrChunk(KEENTALK1PIC);
+
+	US_CenterWindow(26, 8);
+	VWB_DrawPic(WindowX+WindowW-48, WindowY, KEENTALK1PIC);
+	WindowW -= 48;
+	PrintY += 12;
+	US_CPrint("I can't swim!");
+	VW_UpdateScreen();
+	VW_WaitVBL(30);
+	IN_ClearKeysDown();
+	IN_Ack();
+	CA_DownLevel();
+
+	//Note: scorebox sprite has not been re-cached here (didn't use CA_CacheMarks or anything else that would have made the sprite purgable)
+}
+
+//============================================================================
+
+/*
+===========================
+=
+= GotScuba
+=
+===========================
+*/
+
+void GotScuba(void)
+{
+	SD_WaitSoundDone();
+	CA_UpLevel();
+	CA_MarkGrChunk(KEENTALK1PIC);
+	CA_MarkGrChunk(KEENTALK2PIC);
+	CA_CacheMarks(NULL);
+
+	US_CenterWindow(26, 8);
+	VWB_DrawPic(WindowX+WindowW-48, WindowY, KEENTALK1PIC);
+	WindowW -= 48;
+	PrintY += 12;
+	US_CPrint(
+		"Cool!  I can breathe\n"
+		"under water now!"
+		);
+	VW_UpdateScreen();
+	VW_WaitVBL(30);
+	IN_ClearKeysDown();
+	IN_Ack();
+
+	VWB_DrawPic(WindowX+WindowW, WindowY, KEENTALK2PIC);
+	VW_UpdateScreen();
+	VW_WaitVBL(30);
+	IN_ClearKeysDown();
+	IN_Ack();
+
+	CA_DownLevel();
+
+	//Note: scorebox sprite may have been re-cached by CA_DownLevel, but the level ends after this anyway
+}
+
+//============================================================================
+
+/*
+===========================
+=
+= RescuedMember
+=
+===========================
+*/
+
+char *keentext[] = {
+	"No sweat, oh guardian\n"
+	"of wisdom!"
+	,
+	"Sounds like a plan,\n"
+	"bearded one!"
+	,
+	"No problemo."
+	,
+	"Great.  You know, you\n"
+	"look a lot like the\n"
+	"last guy I rescued..."
+	,
+	"Good idea, Gramps."
+	,
+	"May the road rise\n"
+	"to meet your feet,\n"
+	"Mr. Member."
+	,
+	"Wise plan of action,\n"
+	"your ancientness."
+	,
+	"You're the last one,\n"
+	"fella.  Let's both\n"
+	"get back to the\n"
+	"Oracle chamber!"
+};
+
+void RescuedMember(void)
+{
+	SD_WaitSoundDone();
+	CA_UpLevel();
+	CA_MarkGrChunk(ORACLEPIC);
+	CA_MarkGrChunk(KEENTALK1PIC);
+	CA_MarkGrChunk(KEENTALK2PIC);
+	CA_CacheMarks(NULL);
+	StartMusic(-1);
+	VW_FixRefreshBuffer();
+
+	US_CenterWindow(26, 8);
+	VWB_DrawPic(WindowX, WindowY, ORACLEPIC);
+	PrintY += 6;
+	WindowW -= 48;
+	WindowX += 48;
+	if (mapon == 17)
+	{
+		US_CPrint(
+			"Ggoh thig you sogh mg\n"
+			"fgor regscuing mgge!\n"
+			"I'gll regur tgo the\n"
+			"Goracle chagber\n"
+			"igmediatggely. Blub."
+			);
+	}
+	else
+	{
+		US_CPrint(
+			"Oh thank you so much\n"
+			"for rescuing me!\n"
+			"I'll return to the\n"
+			"Oracle chamber\n"
+			"immediately."
+			);
+	}
+	VW_UpdateScreen();
+	VW_WaitVBL(60);
+	IN_ClearKeysDown();
+	IN_Ack();
+
+	US_CenterWindow(26, 8);
+	VWB_DrawPic(WindowX+WindowW-48, WindowY, KEENTALK1PIC);
+	WindowW -= 48;
+	PrintY += 12;
+	US_CPrint(keentext[gamestate.rescued]);
+	VW_UpdateScreen();
+	VW_WaitVBL(30);
+	IN_ClearKeysDown();
+	IN_Ack();
+
+	VWB_DrawPic(WindowX+WindowW, WindowY, KEENTALK2PIC);
+	VW_UpdateScreen();
+	VW_WaitVBL(30);
+	IN_ClearKeysDown();
+	IN_Ack();
+
+	gamestate.rescued++;
+	CA_DownLevel();
+	StopMusic();
+
+	//Note: scorebox sprite may have been re-cached by CA_DownLevel, but the level ends after this anyway
+}
+
+/*
+=============================================================================
+
+						  SWIMMING KEEN
+
+temp4 = counter for spawning bubbles
+
+=============================================================================
+*/
+
+statetype s_keenswimslow1 = {SCUBAKEENL1SPR, SCUBAKEENR1SPR, stepthink, false, false, 50, 0, 0, T_KeenSwimSlow, C_KeenSwim, R_KeenSwim, &s_keenswimslow2};
+statetype s_keenswimslow2 = {SCUBAKEENL2SPR, SCUBAKEENR2SPR, stepthink, false, false, 50, 0, 0, T_KeenSwimSlow, C_KeenSwim, R_KeenSwim, &s_keenswimslow1};
+statetype s_keenswim1     = {SCUBAKEENL1SPR, SCUBAKEENR1SPR, stepthink, false, false, 50, 0, 0, T_KeenSwim, C_KeenSwim, R_KeenSwim, &s_keenswimslow2};
+statetype s_keenswim2     = {SCUBAKEENL2SPR, SCUBAKEENR2SPR, stepthink, false, false, 50, 0, 0, T_KeenSwim, C_KeenSwim, R_KeenSwim, &s_keenswimslow1};
+//Note: the die states for swimming Keen are in CK_KEEN.C and K4_ACT3.C (dopefish section)
+
+statetype s_kbubble1  = {SMALLBUBBLE1SPR, SMALLBUBBLE1SPR, think, false, false, 20, 0, 24, T_Bubble, NULL, R_Draw, &s_kbubble1};
+statetype s_kbubble2  = {SMALLBUBBLE2SPR, SMALLBUBBLE2SPR, think, false, false, 20, 0, 24, T_Bubble, NULL, R_Draw, &s_kbubble2};
+statetype s_kbubble3  = {SMALLBUBBLE3SPR, SMALLBUBBLE3SPR, think, false, false, 20, 0, 24, T_Bubble, NULL, R_Draw, &s_kbubble3};
+statetype s_kbubble4  = {SMALLBUBBLE4SPR, SMALLBUBBLE4SPR, think, false, false, 20, 0, 24, T_Bubble, NULL, R_Draw, &s_kbubble4};
+
+/*
+===========================
+=
+= SpawnSwimKeen
+=
+===========================
+*/
+
+void SpawnSwimKeen(Sint16 x, Sint16 y)
+{
+	player->obclass = keenobj;
+	player->active = ac_allways;
+	player->priority = 1;
+	player->x = CONVERT_TILE_TO_GLOBAL(x);
+	player->y = CONVERT_TILE_TO_GLOBAL(y);
+	player->xdir = 1;
+	player->ydir = 1;
+	player->needtoclip = cl_fullclip;
+	NewState(player, &s_keenswimslow1);
+}
+
+/*
+===========================
+=
+= SpawnKbubble
+=
+===========================
+*/
+
+void SpawnKbubble(objtype *ob)
+{
+	ob->temp4 = 0;
+	GetNewObj(true);
+	if (ob->xdir == -1)
+	{
+		new->x = ob->x;
+	}
+	else
+	{
+		new->x = ob->x + 24*PIXGLOBAL;
+	}
+	new->y = ob->y;
+	new->obclass = inertobj;
+	new->priority = 3;
+	new->active = ac_removable;
+	new->needtoclip = cl_noclip;
+	new->yspeed = -24;
+	new->xspeed = 4;
+	switch (US_RndT() / 64)
+	{
+	case 0:
+		NewState(new, &s_kbubble1);
+		break;
+	case 1:
+		NewState(new, &s_kbubble2);
+		break;
+	case 2:
+		NewState(new, &s_kbubble3);
+		break;
+	case 3:
+		NewState(new, &s_kbubble4);
+		break;
+	}
+	SD_PlaySound(SND_BLUB);
+}
+
+/*
+===========================
+=
+= T_KeenSwimSlow
+=
+===========================
+*/
+
+void T_KeenSwimSlow(objtype *ob)
+{
+	Sint32 i;
+	Sint16 vx, vy, xc, yc;
+
+	xc = ob->xspeed < 0;
+	yc = ob->yspeed < 4;
+
+	ob->temp4 = ob->temp4 + tics;
+	if (ob->temp4 > 60)
+		SpawnKbubble(ob);
+
+	if (jumpbutton && !jumpheld)
+	{
+		jumpheld = true;
+		if (c.xaxis)
+			ob->xspeed = c.xaxis * 18;
+		if (c.yaxis)
+			ob->yspeed = c.yaxis * 18;
+		ob->state = ob->state->nextstate;
+	}
+	if (c.xaxis)
+		ob->xdir = c.xaxis;
+
+	for (i = lasttimecount-tics; i < lasttimecount; i++)
+	{
+		if ((i & 7) == 0)
+		{
+			if (ob->xspeed > 12)
+			{
+				vx = -3;
+			}
+			else if (ob->xspeed > 0)
+			{
+				vx = -1;
+			}
+			else if (ob->xspeed > -12)
+			{
+				vx = 1;
+			}
+			else
+			{
+				vx = 3;
+			}
+			vx += c.xaxis;
+			vx += c.xaxis;
+			ob->xspeed += vx;
+
+			if (c.xaxis == 0 && (ob->xspeed < 0) != xc)
+				ob->xspeed = 0;
+
+			if (ob->yspeed > 12)
+			{
+				vy = -3;
+			}
+			else if (ob->yspeed > 4)
+			{
+				vy = -1;
+			}
+			else if (ob->yspeed > -12)
+			{
+				vy = 1;
+			}
+			else
+			{
+				vy = 3;
+			}
+			vy += c.yaxis;
+			vy += c.yaxis;
+			ob->yspeed += vy;
+
+			if (c.yaxis == 0 && ob->yspeed > 4 && yc)
+				ob->yspeed = 0;
+		}
+		xtry += ob->xspeed;
+		ytry += ob->yspeed;
+	}
+}
+
+/*
+===========================
+=
+= T_KeenSwim
+=
+===========================
+*/
+
+void T_KeenSwim(objtype *ob)	//never actually used
+{
+	ob->temp4 = ob->temp4 + tics;
+	if (ob->temp4 > 60)
+		SpawnKbubble(ob);
+
+	if (jumpbutton && !jumpheld)
+	{
+		jumpheld = true;
+		ob->xspeed = c.xaxis * 18;
+		if (c.yaxis)
+			ob->yspeed = c.yaxis * 18;
+
+		if (ob->state == &s_keenswim1)
+		{
+			ob->state = &s_keenswim2;
+		}
+		else
+		{
+			ob->state = &s_keenswim1;
+		}
+	}
+
+	xtry = xtry + ob->xspeed * tics;
+	ytry = ytry + ob->yspeed * tics;
+	if (xtry > 0)
+	{
+		ob->xdir = 1;
+	}
+	else if (xtry < 0)
+	{
+		ob->xdir = -1;
+	}
+
+	ytry = ytry + tics*4;
+}
+
+/*
+===========================
+=
+= C_KeenSwim
+=
+===========================
+*/
+
+void C_KeenSwim(objtype *ob, objtype *hit)
+{
+	switch (hit->obclass)
+	{
+	case bonusobj:
+		switch (hit->temp1)
+		{
+		case 0:
+		case 1:
+		case 2:
+		case 3:
+		case 4:
+		case 5:
+		case 6:
+		case 7:
+		case 8:
+		case 9:
+		case 10:
+		case 11:
+			SD_PlaySound(bonussound[hit->temp1]);
+			hit->obclass = inertobj;
+			hit->priority = 3;
+			hit->shapenum = bonussprite[hit->temp1];
+			GivePoints(bonuspoints[hit->temp1]);
+			if (hit->temp1 < 4)
+			{
+				gamestate.keys[hit->temp1]++;
+			}
+			else if (hit->temp1 == 10)
+			{
+				gamestate.lives++;
+			}
+			else if (hit->temp1 == 11)
+			{
+				gamestate.ammo += shotsinclip[gamestate.difficulty];
+			}
+			ChangeState(hit, &s_bonusrise);
+			break;
+		}
+		break;
+
+	case oracleobj:
+		playstate = ex_rescued;
+		break;
+	}
+	ob++;			// shut up compiler
+}
+
+/*
+===========================
+=
+= R_KeenSwim
+=
+===========================
+*/
+
+void R_KeenSwim(objtype *ob)
+{
+	if (ob->hiteast && ob->xspeed < 0 || ob->hitwest && ob->xspeed > 0)
+		ob->xspeed = 0;
+
+	if (ob->hitnorth && ob->yspeed > 0 || ob->hitsouth && ob->yspeed < 0)
+		ob->yspeed = 0;
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
diff --git a/16/keen456/KEEN4-6/KEEN4C/GFXC_CK4.EQU b/16/keen456/KEEN4-6/KEEN4C/GFXC_CK4.EQU
new file mode 100755
index 00000000..44440397
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN4C/GFXC_CK4.EQU
@@ -0,0 +1,55 @@
+;=====================================
+;
+; Graphics .EQU file for .CK4
+; not IGRAB-ed :)
+;
+;=====================================
+
+;INCLUDE "VERSION.EQU"
+
+;
+; Amount of each data item
+;
+NUMFONT     =	2
+NUMFONTM    =	0
+NUMPICM     =	3
+NUMTILE8    =	108
+NUMTILE8M   =	36
+NUMTILE32   =	0
+NUMTILE32M  =	0
+
+;
+; Amount of each item in episode 4
+;
+NUMPICS     =	116
+NUMSPRITES  =	397
+NUMTILE16   =	1296
+NUMTILE16M  =	2916
+NUMEXTERN   =	16
+
+
+;
+; File offsets for data items
+;
+STRUCTPIC       =	0
+STRUCTPICM      =	1
+STRUCTSPRITE    =	2
+
+STARTFONT       =	3
+STARTFONTM      =	(STARTFONT+NUMFONT)
+STARTPICS       =	(STARTFONTM+NUMFONTM)
+STARTPICM       =	(STARTPICS+NUMPICS)
+STARTSPRITES    =	(STARTPICM+NUMPICM)
+STARTTILE8      =	(STARTSPRITES+NUMSPRITES)
+STARTTILE8M     =	(STARTTILE8+1)
+STARTTILE16     =	(STARTTILE8M+1)
+STARTTILE16M    =	(STARTTILE16+NUMTILE16)
+STARTTILE32     =	(STARTTILE16M+NUMTILE16M)
+STARTTILE32M    =	(STARTTILE32+NUMTILE32)
+STARTEXTERN     =	(STARTTILE32M+NUMTILE32M)
+
+NUMCHUNKS       =	(STARTEXTERN+NUMEXTERN)
+
+;
+; Thank you for using IGRAB!
+;
diff --git a/16/keen456/KEEN4-6/KEEN4C/GFXC_CK4.H b/16/keen456/KEEN4-6/KEEN4C/GFXC_CK4.H
new file mode 100755
index 00000000..02585642
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN4C/GFXC_CK4.H
@@ -0,0 +1,767 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+#ifndef __GFX_H__
+#define __GFX_H__
+
+//#include "VERSION.H"
+
+//////////////////////////////////////
+//
+// Graphics .H file for .CK4
+// not IGRAB-ed :)
+//
+//////////////////////////////////////
+
+//
+// Lump creation macros
+//
+
+#define START_LUMP(actualname, dummyname) actualname, dummyname=actualname-1,
+#define END_LUMP(actualname, dummyname) dummyname, actualname=dummyname-1,
+
+//
+// Amount of each data item
+//
+
+//common numbers:
+#define NUMCHUNKS    NUMGRCHUNKS
+#define NUMFONT      2
+#define NUMFONTM     0
+#define NUMPICM      3
+#define NUMTILE8     108	// BUG: only 104 tiles exist in EGAGRAPH!
+#define NUMTILE8M    36		// BUG: only 20 tiles exist in EGAGRAPH!
+#define NUMTILE32    0
+#define NUMTILE32M   0
+
+//episode-specific numbers:
+#define NUMPICS      116
+#define NUMSPRITES   397
+#define NUMTILE16    1296
+#define NUMTILE16M   2916
+#define NUMEXTERNS   16
+
+//
+// File offsets for data items
+//
+#define STRUCTPIC    0
+#define STRUCTPICM   1
+#define STRUCTSPRITE 2
+
+#define STARTFONT    3
+#define STARTFONTM   (STARTFONT+NUMFONT)
+#define STARTPICS    (STARTFONTM+NUMFONTM)
+#define STARTPICM    (STARTPICS+NUMPICS)
+#define STARTSPRITES (STARTPICM+NUMPICM)
+#define STARTTILE8   (STARTSPRITES+NUMSPRITES)
+#define STARTTILE8M  (STARTTILE8+1)
+#define STARTTILE16  (STARTTILE8M+1)
+#define STARTTILE16M (STARTTILE16+NUMTILE16)
+#define STARTTILE32  (STARTTILE16M+NUMTILE16M)
+#define STARTTILE32M (STARTTILE32+NUMTILE32)
+#define STARTEXTERNS (STARTTILE32M+NUMTILE32M)
+
+typedef enum {
+	LASTFONT=STARTPICS-1,
+
+	//
+	// PICS
+	//
+
+	PADDINGPIC,                  // 5 (compensate for the missing Star Wars font to give the other pics the correct chunk numbers)
+
+	H_HELPPIC,                   // 6
+	H_LARROWPIC,                 // 7
+	H_RARROWPIC,                 // 8
+	H_ESCPIC,                    // 9
+	H_ENTERPIC,                  // 10
+	DUMMYPIC,                    // 11
+	H_STORY1PIC,                 // 12
+	H_STORY2PIC,                 // 13
+	H_STORY3PIC,                 // 14
+	H_STORY4PIC,                 // 15
+	STORY5PIC,                   // 16
+	STORY6PIC,                   // 17
+	STORY7PIC,                   // 18
+	STORY8PIC,                   // 19
+	ITEM1PIC,                    // 20
+	ITEM2PIC,                    // 21
+	ITEM3PIC,                    // 22
+	ITEM4PIC,                    // 23
+	ITEM5PIC,                    // 24
+	ITEM6PIC,                    // 25
+	ITEM7PIC,                    // 26
+	ITEM8PIC,                    // 27
+	ITEM9PIC,                    // 28
+	ARACHNUTPIC,                 // 29
+	BERKELOISPIC,                // 30
+	BOUNDERPIC,                  // 31
+	COUNCILMEMBERPIC,            // 32
+	DOPEFISHPIC,                 // 33
+	INCHWORMPIC,                 // 34
+	LICKPIC,                     // 35
+	MADMUSHROOMPIC,              // 36
+	POISONSLIGPIC,               // 37
+	PRINCESSLINDSEYPIC,          // 38
+	SCHOOLFISHPIC,               // 39
+	SKYPESTPIC,                  // 40
+	SPRITEPIC,                   // 41
+	WORMOUTHPIC,                 // 42
+	ENDOFTEXTPIC,                // 43
+	H_MCPIC,                     // 44
+	H_HANDPIC,                   // 45
+	H_VISAPIC,                   // 46
+	H_FLASHARROW1PIC,            // 47
+	H_FLASHARROW2PIC,            // 48
+	ENDINDG1PIC,                 // 49
+	ENDINDG2PIC,                 // 50
+	ENDINDG3PIC,                 // 51
+	ENDINDG4PIC,                 // 52
+	ENDINDG5PIC,                 // 53
+	ENDINDG6PIC,                 // 54
+	ENDINDG7PIC,                 // 55
+	ENDINDG8PIC,                 // 56
+	ENDINDG9PIC,                 // 57
+	ENDINDG10PIC,                // 58
+	ENDINDG11PIC,                // 59
+	ENDINDG12PIC,                // 60
+	ENDINDG13PIC,                // 61
+	ENDINDG14PIC,                // 62
+	ENDINDG15PIC,                // 63
+	ENDINDG16PIC,                // 64
+	ENDINDG17PIC,                // 65
+	ENDINDG18PIC,                // 66
+	ENDINDG19PIC,                // 67
+	ENDINDG20PIC,                // 68
+	ENDINDG21PIC,                // 69
+	ENDINDG22PIC,                // 70
+	ENDINDG23PIC,                // 71
+	ENDINDG24PIC,                // 72
+	ENDINDG25PIC,                // 73
+	ENDINDG26PIC,                // 74
+	ENDINDG27PIC,                // 75
+	ENDINDG28PIC,                // 76
+	ENDINDG29PIC,                // 77
+	ENDINDG30PIC,                // 78
+	H_IDLOGOPIC,                 // 79
+	H_TOPWINDOWPIC,              // 80
+	H_LEFTWINDOWPIC,             // 81
+	H_RIGHTWINDOWPIC,            // 82
+	H_BOTTOMINFOPIC,             // 83
+	H_BOTTOMWINDOWPIC,           // 84
+	H_BARPIC,                    // 85
+	H_KEEN5PIC,                  // 86
+	H_KEEN6PIC,                  // 87
+
+	START_LUMP(CONTROLS_LUMP_START, __CONTROLSSTART)
+	CP_MAINMENUPIC,              // 88
+	CP_NEWGAMEMENUPIC,           // 89
+	CP_LOADMENUPIC,              // 90
+	CP_SAVEMENUPIC,              // 91
+	CP_CONFIGMENUPIC,            // 92
+	CP_SOUNDMENUPIC,             // 93
+	CP_MUSICMENUPIC,             // 94
+	CP_KEYBOARDMENUPIC,          // 95
+	CP_KEYMOVEMENTPIC,           // 96
+	CP_KEYBUTTONPIC,             // 97
+	CP_JOYSTICKMENUPIC,          // 98
+	CP_OPTIONSMENUPIC,           // 99
+	CP_PADDLEWARPIC,             // 100
+	CP_QUITPIC,                  // 101
+	CP_JOYSTICKPIC,              // 102
+	CP_MENUSCREENPIC,            // 103
+	END_LUMP(CONTROLS_LUMP_END, __CONTROLSEND)
+
+	IDSOFTPIC,                   // 104
+	PROGTEAMPIC,                 // 105
+	ARTISTPIC,                   // 106
+	DIRECTORPIC,                 // 107
+	SW_BACKGROUNDPIC,            // 108
+	TITLEPICPIC,                 // 109
+	ORACLEPIC,                   // 110
+	KEENTALK1PIC,                // 111
+	KEENTALK2PIC,                // 112
+	KEENMADPIC,                  // 113
+	LINDSEYPIC,                  // 114
+	KEENCOUNT1PIC,               // 115
+	KEENCOUNT2PIC,               // 116
+	KEENCOUNT3PIC,               // 117
+	KEENCOUNT4PIC,               // 118
+	KEENCOUNT5PIC,               // 119
+	KEENCOUNT6PIC,               // 120
+
+	//
+	// MASKED PICS
+	//
+
+	CP_MENUMASKPICM,             // 121
+	CORDPICM,                    // 122
+	METALPOLEPICM,               // 123
+
+	//
+	// SPRITES
+	//
+
+	START_LUMP(PADDLE_LUMP_START, __PADDLESTART)
+	PADDLESPR,                   // 124
+	BALLSPR,                     // 125
+	BALL1PIXELTOTHERIGHTSPR,     // 126
+	BALL2PIXELSTOTHERIGHTSPR,    // 127
+	BALL3PIXELSTOTHERIGHTSPR,    // 128
+	END_LUMP(PADDLE_LUMP_END, __PADDLEEND)
+
+	DEMOPLAQUESPR,               // 129
+
+	//player lump:
+	START_LUMP(KEEN_LUMP_START, __KEENSTART)
+	KEENSTANDRSPR,               // 130
+	KEENRUNR1SPR,                // 131
+	KEENRUNR2SPR,                // 132
+	KEENRUNR3SPR,                // 133
+	KEENRUNR4SPR,                // 134
+	KEENJUMPR1SPR,               // 135
+	KEENJUMPR2SPR,               // 136
+	KEENJUMPR3SPR,               // 137
+	KEENSTANDLSPR,               // 138
+	KEENRUNL1SPR,                // 139
+	KEENRUNL2SPR,                // 140
+	KEENRUNL3SPR,                // 141
+	KEENRUNL4SPR,                // 142
+	KEENJUMPL1SPR,               // 143
+	KEENJUMPL2SPR,               // 144
+	KEENJUMPL3SPR,               // 145
+	KEENLOOKUSPR,                // 146
+	KEENWAITR1SPR,               // 147
+	KEENWAITR2SPR,               // 148
+	KEENWAITR3SPR,               // 149
+	KEENSITREAD1SPR,             // 150
+	KEENSITREAD2SPR,             // 151
+	KEENSITREAD3SPR,             // 152
+	KEENSITREAD4SPR,             // 153
+	KEENREAD1SPR,                // 154
+	KEENREAD2SPR,                // 155
+	KEENREAD3SPR,                // 156
+	KEENSTOPREAD1SPR,            // 157
+	KEENSTOPREAD2SPR,            // 158
+	KEENWATCHSPR,                // 159
+	KEENLOOKD1SPR,               // 160
+	KEENLOOKD2SPR,               // 161
+	KEENDIE1SPR,                 // 162
+	KEENDIE2SPR,                 // 163
+	STUNSTARS1SPR,               // 164
+	STUNSTARS2SPR,               // 165
+	STUNSTARS3SPR,               // 166
+	KEENSHOOTLSPR,               // 167
+	KEENJLSHOOTLSPR,             // 168
+	KEENJSHOOTDSPR,              // 169
+	KEENJSHOOTUSPR,              // 170
+	KEENSHOOTUSPR,               // 171
+	KEENSHOOTRSPR,               // 172
+	KEENJRSHOOTRSPR,             // 173
+	STUN1SPR,                    // 174
+	STUN2SPR,                    // 175
+	STUN3SPR,                    // 176
+	STUN4SPR,                    // 177
+	STUNHIT1SPR,                 // 178
+	STUNHIT2SPR,                 // 179
+	KEENSHINNYR1SPR,             // 180
+	KEENSHINNYR2SPR,             // 181
+	KEENSHINNYR3SPR,             // 182
+	KEENSLIDED1SPR,              // 183
+	KEENSLIDED2SPR,              // 184
+	KEENSLIDED3SPR,              // 185
+	KEENSLIDED4SPR,              // 186
+	KEENSHINNYL1SPR,             // 187
+	KEENSHINNYL2SPR,             // 188
+	KEENSHINNYL3SPR,             // 189
+	KEENPLSHOOTUSPR,             // 190
+	KEENPRSHOOTUSPR,             // 191
+	KEENPRSHOOTDSPR,             // 192
+	KEENPLSHOOTDSPR,             // 193
+	KEENPSHOOTLSPR,              // 194
+	KEENPSHOOTRSPR,              // 195
+	KEENENTER1SPR,               // 196
+	KEENENTER2SPR,               // 197
+	KEENENTER3SPR,               // 198
+	KEENENTER4SPR,               // 199
+	KEENENTER5SPR,               // 200
+	KEENHANGLSPR,                // 201
+	KEENHANGRSPR,                // 202
+	KEENCLIMBEDGEL1SPR,          // 203
+	KEENCLIMBEDGEL2SPR,          // 204
+	KEENCLIMBEDGEL3SPR,          // 205
+	KEENCLIMBEDGEL4SPR,          // 206
+	KEENCLIMBEDGER1SPR,          // 207
+	KEENCLIMBEDGER2SPR,          // 208
+	KEENCLIMBEDGER3SPR,          // 209
+	KEENCLIMBEDGER4SPR,          // 210
+	KEENPOGOR1SPR,               // 211
+	KEENPOGOR2SPR,               // 212
+	KEENPOGOL1SPR,               // 213
+	KEENPOGOL2SPR,               // 214
+	DROPSPLASH1SPR,              // 215
+	DROPSPLASH2SPR,              // 216
+	DROPSPLASH3SPR,              // 217
+	BONUS100UPSPR,               // 218
+	BONUS100SPR,                 // 219
+	BONUS200SPR,                 // 220
+	BONUS500SPR,                 // 221
+	BONUS1000SPR,                // 222
+	BONUS2000SPR,                // 223
+	BONUS5000SPR,                // 224
+	BONUS1UPSPR,                 // 225
+	BONUSCLIPSPR,                // 226
+	END_LUMP(KEEN_LUMP_END, __KEENEND)
+
+	START_LUMP(SUGAR1_LUMP_START, __SUGAR1START)
+	SUGAR1ASPR,                  // 227
+	SUGAR1BSPR,                  // 228
+	END_LUMP(SUGAR1_LUMP_END, __SUGAR1END)
+
+	START_LUMP(SUGAR2_LUMP_START, __SUGAR2START)
+	SUGAR2ASPR,                  // 229
+	SUGAR2BSPR,                  // 230
+	END_LUMP(SUGAR2_LUMP_END, __SUGAR2END)
+
+	START_LUMP(SUGAR3_LUMP_START, __SUGAR3START)
+	SUGAR3ASPR,                  // 231
+	SUGAR3BSPR,                  // 232
+	END_LUMP(SUGAR3_LUMP_END, __SUGAR3END)
+
+	START_LUMP(SUGAR4_LUMP_START, __SUGAR4START)
+	SUGAR4ASPR,                  // 233
+	SUGAR4BSPR,                  // 234
+	END_LUMP(SUGAR4_LUMP_END, __SUGAR4END)
+
+	START_LUMP(SUGAR5_LUMP_START, __SUGAR5START)
+	SUGAR5ASPR,                  // 235
+	SUGAR5BSPR,                  // 236
+	END_LUMP(SUGAR5_LUMP_END, __SUGAR5END)
+
+	START_LUMP(SUGAR6_LUMP_START, __SUGAR6START)
+	SUGAR6ASPR,                  // 237
+	SUGAR6BSPR,                  // 238
+	END_LUMP(SUGAR6_LUMP_END, __SUGAR6END)
+
+	START_LUMP(ONEUP_LUMP_START, __ONEUPSTART)
+	ONEUPASPR,                   // 239
+	ONEUPBSPR,                   // 240
+	END_LUMP(ONEUP_LUMP_END, __ONEUPEND)
+
+	DOORSPR,                     // 241
+
+	START_LUMP(KEYGEM_LUMP_START, __KEYGEMSTART)
+	REDGEM1SPR,                  // 242
+	REDGEM2SPR,                  // 243
+	YELLOWGEM1SPR,               // 244
+	YELLOWGEM2SPR,               // 245
+	BLUEGEM1SPR,                 // 246
+	BLUEGEM2SPR,                 // 247
+	GREENGEM1SPR,                // 248
+	GREENGEM2SPR,                // 249
+	BONUSGEMSPR,                 // 250
+	END_LUMP(KEYGEM_LUMP_END, __KEYGEMEND)
+
+	START_LUMP(AMMO_LUMP_START, __AMMOSTART)
+	STUNCLIP1SPR,                // 251
+	STUNCLIP2SPR,                // 252
+	END_LUMP(AMMO_LUMP_END, __AMMOEND)
+
+	SCOREBOXSPR,                 // 253
+
+	START_LUMP(WORLDKEEN_LUMP_START, __WORLDKEENSTART)
+	WORLDKEENL1SPR,              // 254
+	WORLDKEENL2SPR,              // 255
+	WORLDKEENL3SPR,              // 256
+	WORLDKEENR1SPR,              // 257
+	WORLDKEENR2SPR,              // 258
+	WORLDKEENR3SPR,              // 259
+	WORLDKEENU1SPR,              // 260
+	WORLDKEENU2SPR,              // 261
+	WORLDKEENU3SPR,              // 262
+	WORLDKEEND1SPR,              // 263
+	WORLDKEEND2SPR,              // 264
+	WORLDKEEND3SPR,              // 265
+	WORLDKEENDR1SPR,             // 266
+	WORLDKEENDR2SPR,             // 267
+	WORLDKEENDR3SPR,             // 268
+	WORLDKEENDL1SPR,             // 269
+	WORLDKEENDL2SPR,             // 270
+	WORLDKEENDL3SPR,             // 271
+	WORLDKEENUL1SPR,             // 272
+	WORLDKEENUL2SPR,             // 273
+	WORLDKEENUL3SPR,             // 274
+	WORLDKEENUR1SPR,             // 275
+	WORLDKEENUR2SPR,             // 276
+	WORLDKEENUR3SPR,             // 277
+	WORLDKEENWAVE1SPR,           // 278
+	WORLDKEENWAVE2SPR,           // 279
+	WORLDKEENSWIMU1SPR,          // 280
+	WORLDKEENSWIMU2SPR,          // 281
+	WORLDKEENSWIMR1SPR,          // 282
+	WORLDKEENSWIMR2SPR,          // 283
+	WORLDKEENSWIMD1SPR,          // 284
+	WORLDKEENSWIMD2SPR,          // 285
+	WORLDKEENSWIML1SPR,          // 286
+	WORLDKEENSWIML2SPR,          // 287
+	WORLDKEENSWIMUR1SPR,         // 288
+	WORLDKEENSWIMUR2SPR,         // 289
+	WORLDKEENSWIMDR1SPR,         // 290
+	WORLDKEENSWIMDR2SPR,         // 291
+	WORLDKEENSWIMDL1SPR,         // 292
+	WORLDKEENSWIMDL2SPR,         // 293
+	WORLDKEENSWIMUL1SPR,         // 294
+	WORLDKEENSWIMUL2SPR,         // 295
+	WOLRDKEENRIDE1SPR,           // 296
+	WOLRDKEENRIDE2SPR,           // 297
+	FLAGFLIP1SPR,                // 298
+	FLAGFLIP2SPR,                // 299
+	FLAGFLIP3SPR,                // 300
+	FLAGFLIP4SPR,                // 301
+	FLAGFLIP5SPR,                // 302
+	FLAGFALL1SPR,                // 303
+	FLAGFALL2SPR,                // 304
+	FLAGFLAP1SPR,                // 305
+	FLAGFLAP2SPR,                // 306
+	FLAGFLAP3SPR,                // 307
+	FLAGFLAP4SPR,                // 308
+	END_LUMP(WORLDKEEN_LUMP_END, __WORLDKEENEND)
+
+	START_LUMP(SCUBAKEEN_LUMP_START, __SCUBAKEENSTART)
+	SCUBAKEENL1SPR,              // 309
+	SCUBAKEENL2SPR,              // 310
+	SCUBAKEENR1SPR,              // 311
+	SCUBAKEENR2SPR,              // 312
+	SCUBAKEENDEAD1SPR,           // 313
+	SCUBAKEENDEAD2SPR,           // 314
+	END_LUMP(SCUBAKEEN_LUMP_END, __SCUBAKEENEND)
+
+	START_LUMP(SLUG_LUMP_START, __SLUGSTART)
+	SLUGWALKR1SPR,               // 315
+	SLUGWALKR2SPR,               // 316
+	SLUGPISSRSPR,                 // 317
+	SLUGSTUN1SPR,             // 318
+	SLUGSTUN2SPR,             // 319
+	SLUGWALKL1SPR,               // 320
+	SLUGWALKL2SPR,               // 321
+	SLUGPISSLSPR,                 // 322
+	SLUGSLIME1SPR,               // 323
+	SLUGSLIME2SPR,               // 324
+	END_LUMP(SLUG_LUMP_END, __SLUGEND)
+
+	START_LUMP(MADMUSHROOM_LUMP_START, __MADMUSHROOMSTART)
+	MADMUSHROOML1SPR,            // 325
+	MADMUSHROOML2SPR,            // 326
+	MADMUSHROOMR1SPR,            // 327
+	MADMUSHROOMR2SPR,            // 328
+	END_LUMP(MADMUSHROOM_LUMP_END, __MADMUSHROOMEND)
+
+	START_LUMP(LINDSEY_LUMP_START, __LINDSEYSTART)
+	LINDSEY1SPR,                 // 329
+	LINDSEY2SPR,                 // 330
+	LINDSEY3SPR,                 // 331
+	LINDSEY4SPR,                 // 332
+	END_LUMP(LINDSEY_LUMP_END, __LINDSEYEND)
+
+	START_LUMP(INCHWORM_LUMP_START, __INCHWORMSTART)
+	INCHWORMR1SPR,               // 333
+	INCHWORMR2SPR,               // 334
+	INCHWORML1SPR,               // 335
+	INCHWORML2SPR,               // 336
+	FOOTSPR,                     // 337
+	END_LUMP(INCHWORM_LUMP_END, __INCHWORMEND)
+
+	START_LUMP(EATER_LUMP_START, __EATERSTART)
+	EATERSTAND1SPR,              // 338
+	EATERSTAND2SPR,              // 339
+	EATERJUMPR1SPR,              // 340
+	EATERJUMPR2SPR,              // 341
+	EATERJUMPR3SPR,              // 342
+	EATERJUMPL1SPR,              // 343
+	EATERJUMPL2SPR,              // 344
+	EATERJUMPL3SPR,              // 345
+	EATENBONUS1SPR,              // 346
+	EATENBONUS2SPR,              // 347
+	EATENBONUS3SPR,              // 348
+	EATENBONUS4SPR,              // 349
+	SMOKE1SPR,                   // 350
+	SMOKE2SPR,                   // 351
+	SMOKE3SPR,                   // 352
+	SMOKE4SPR,                   // 353
+	SMOKE5SPR,                   // 354
+	EATERSTUNSPR,                // 355
+	END_LUMP(EATER_LUMP_END, __EATEREND)
+
+	START_LUMP(COUNCIL_LUMP_START, __COUINCILSTART)
+	COUNCILWALKR1SPR,            // 356
+	COUNCILWALKR2SPR,            // 357
+	COUNCILWALKL1SPR,            // 358
+	COUNCILWALKL2SPR,            // 359
+	COUNCILTHINKLSPR,            // 360
+	COUNCILTHINKRSPR,            // 361
+	END_LUMP(COUNCIL_LUMP_END, __COUNCILEND)
+
+	START_LUMP(EGG_LUMP_START, __EGGSTART)
+	EGGSPR,                      // 362
+	EGGBROKESPR,                // 363
+	EGGCHIP1SPR,                // 364
+	EGGCHIP2SPR,                // 365
+	EGGCHIP3SPR,                // 366
+	END_LUMP(EGG_LUMP_END, __EGGEND)
+
+	START_LUMP(EGGBIRD_LUMP_START, __EGGBIRDSTART)
+	BIRDWALKR1SPR,               // 367
+	BIRDWALKR2SPR,               // 368
+	BIRDWALKR3SPR,               // 369
+	BIRDWALKR4SPR,               // 370
+	BIRDWALKL1SPR,               // 371
+	BIRDWALKL2SPR,               // 372
+	BIRDWALKL3SPR,               // 373
+	BIRDWALKL4SPR,               // 374
+	BIRDFLY1SPR,                 // 375
+	BIRDFLY2SPR,                 // 376
+	BIRDFLY3SPR,                 // 377
+	BIRDFLY4SPR,                 // 378
+	BIRDSTUNSPR,                 // 379
+	END_LUMP(EGGBIRD_LUMP_END, __EGGBIRDEND)
+
+	START_LUMP(DARTS_LUMP_START, __DARTSSTART)
+	DARTU1SPR,                   // 380
+	DARTU2SPR,                   // 381
+	DARTD1SPR,                   // 382
+	DARTD2SPR,                   // 383
+	DARTR1SPR,                   // 384
+	DARTR2SPR,                   // 385
+	DARTL1SPR,                   // 386
+	DARTL2SPR,                   // 387
+	END_LUMP(DARTS_LUMP_END, __DARTSEND)
+
+	START_LUMP(MIMROCK_LUMP_START, __MIMROCKSTART)
+	MIMROCKSPR,                  // 388
+	MIMROCKWALKL1SPR,            // 389
+	MIMROCKWALKL2SPR,            // 390
+	MIMROCKWALKL3SPR,            // 391
+	MIMROCKWALKL4SPR,            // 392
+	MIMROCKWALKR1SPR,            // 393
+	MIMROCKWALKR2SPR,            // 394
+	MIMROCKWALKR3SPR,            // 395
+	MIMROCKWALKR4SPR,            // 396
+	MIMROCKJUMPR1SPR,            // 397
+	MIMROCKJUMPR2SPR,            // 398
+	MIMROCKJUMPR3SPR,            // 399
+	MIMROCKJUMPL1SPR,            // 400
+	MIMROCKJUMPL2SPR,            // 401
+	MIMROCKJUMPL3SPR,            // 402
+	MINROCKSTUNSPR,              // 403
+	END_LUMP(MIMROCK_LUMP_END, __MIMROCKEND)
+
+	START_LUMP(DOPEFISH_LUMP_START, __DOPEFISHSTART)
+	DOPEFISHSWIMR1SPR,           // 404
+	DOPEFISHSWIMR2SPR,           // 405
+	DOPEFISHHUNGRYRSPR,          // 406
+	DOPEFISHBURP1SPR,            // 407
+	DOPEFISHBURP2SPR,            // 408
+	BIGBUBBLE1SPR,               // 409
+	BIGBUBBLE2SPR,               // 410
+	BIGBUBBLE3SPR,               // 411
+	BIGBUBBLE4SPR,               // 412
+	SMALLBUBBLE1SPR,             // 413
+	SMALLBUBBLE2SPR,             // 414
+	SMALLBUBBLE3SPR,             // 415
+	SMALLBUBBLE4SPR,             // 416
+	MEDIUMBUBBLESPR,             // 417
+	DOPEFISHSWIML1SPR,           // 418
+	DOPEFISHSWIML2SPR,           // 419
+	DOPEFISHHUNGRYLSPR,          // 420
+	END_LUMP(DOPEFISH_LUMP_END, __DOPEFISHEND)
+
+	START_LUMP(SCHOOLFISH_LUMP_START, __SCHOOLFISHSTART)
+	SCHOOLFISHL1SPR,             // 421
+	SCHOOLFISHL2SPR,             // 422
+	SCHOOLFISHR1SPR,             // 423
+	SCHOOLFISHR2SPR,             // 424
+	END_LUMP(SCHOOLFISH_LUMP_END, __SCHOOLFISHEND)
+
+	START_LUMP(ARACHNUT_LUMP_START, __ARACHNUTSTART)
+	ARACHNUTWALK1SPR,            // 425
+	ARACHNUTWALK2SPR,            // 426
+	ARACHNUTWALK3SPR,            // 427
+	ARACHNUTWALK4SPR,            // 428
+	ARACHNUTSTUNSPR,             // 429
+	END_LUMP(ARACHNUT_LUMP_END, __ARACHNUTEND)
+
+	SCUBASPR,                    // 430
+
+	START_LUMP(SPRITE_LUMP_START, __SPRITESTART)
+	SPRITEFLOATSPR,              // 431
+	SPRITEAIMLSPR,               // 432
+	SPRITESHOOTLSPR,             // 433
+	SPRITEAIMRSPR,               // 434
+	SPRITESHOOTRSPR,             // 435
+	SPRITESHOT1SPR,              // 436
+	SPRITESHOT2SPR,              // 437
+	SPRITESHOT3SPR,              // 438
+	SPRITESHOT4SPR,              // 439
+	END_LUMP(SPRITE_LUMP_END, __SPRITEEND)
+
+	START_LUMP(MINE_LUMP_START, __MINESTART)
+	MINESPR,                     // 440
+	MINEEXPLODE1SPR,             // 441
+	MINEEXPLODE2SPR,             // 442
+	END_LUMP(MINE_LUMP_END, __MINEEND)
+
+	START_LUMP(SKYPEST_LUMP_START, __SKYPESTSTART)
+	SKYPESTFLYL1SPR,             // 443
+	SKYPESTFLYL2SPR,             // 444
+	SKYPESTFLYR1SPR,             // 445
+	SKYPESTFLYR2SPR,             // 446
+	SKYPESTSIT1SPR,              // 447
+	SKYPESTSIT2SPR,              // 448
+	SKYPESTSIT3SPR,              // 449
+	SKYPESTSIT4SPR,              // 450
+	SKYPESTSIT5SPR,              // 451
+	SKYPESTSIT6SPR,              // 452
+	SKYPESTSIT7SPR,              // 453
+	SKYPESTSIT8SPR,              // 454
+	SKYPESTSIT9SPR,              // 455
+	SKYPESTSQUASHEDSPR,          // 456
+	END_LUMP(SKYPEST_LUMP_END, __SKYPESTEND)
+
+	START_LUMP(WORMOUTH_LUMP_START, __WORMOUTHSTART)
+	WORMOUTHSPR,                 // 457
+	WORMOUTHPEEKR1SPR,           // 458
+	WORMOUTHPEEKR2SPR,           // 459
+	WORMOUTHPEEKL1SPR,           // 460
+	WORMOUTHPEEKL2SPR,           // 461
+	WORMOUTHBITER1SPR,           // 462
+	WORMOUTHBITER2SPR,           // 463
+	WORMOUTHBITER3SPR,           // 464
+	WORMOUTHBITEL1SPR,           // 465
+	WORMOUTHBITEL2SPR,           // 466
+	WORMOUTHBITEL3SPR,           // 467
+	WORMOUTHSTUNSPR,             // 468
+	END_LUMP(WORMOUTH_LUMP_END, __WORMOUTHEND)
+
+	START_LUMP(LICK_LUMP_START, __LICKSTART)
+	LICKMOVER1SPR,               // 469
+	LICKMOVER2SPR,               // 470
+	LICKMOVER3SPR,               // 471
+	LICKMOVER4SPR,               // 472
+	LICKMOVEL1SPR,               // 473
+	LICKMOVEL2SPR,               // 474
+	LICKMOVEL3SPR,               // 475
+	LICKMOVEL4SPR,               // 476
+	LICKATTACKR1SPR,             // 477
+	LICKATTACKR2SPR,             // 478
+	LICKATTACKR3SPR,             // 479
+	LICKATTACKL1SPR,             // 480
+	LICKATTACKL2SPR,             // 481
+	LICKATTACKL3SPR,             // 482
+	LICKSTUNSPR,                 // 483
+	END_LUMP(LICK_LUMP_END, __LICKEND)
+
+	START_LUMP(PLATFORM_LUMP_START, __PLATFORMSTART)
+	PLATFORMSPR,                 // 484
+	PLATSIDETHRUST1SPR,          // 485
+	PLATSIDETHRUST2SPR,          // 486
+	PLATRTHRUST1SPR,             // 487
+	PLATRTHRUST2SPR,             // 488
+	PLATLTHRUST1SPR,             // 489
+	PLATLTHRUST2SPR,             // 490
+	END_LUMP(PLATFORM_LUMP_END, __PLATFORMEND)
+
+	START_LUMP(BOUNDER_LUMP_START, __BOUNDERSTART)
+	BOUNDERL1SPR,                // 491
+	BOUNDERL2SPR,                // 492
+	BOUNDERR1SPR,                // 493
+	BOUNDERR2SPR,                // 494
+	BOUNDERC1SPR,                // 495
+	BOUNDERC2SPR,                // 496
+	BOUNDERSTUNSPR,           // 497
+	END_LUMP(BOUNDER_LUMP_END, __BOUNDEREND)
+
+	START_LUMP(THUNDERCLOUD_LUMP_START, __THUNDERCLOUDSTART)
+	CLOUDSPR,                    // 498
+	CLOUDACTIVESPR,              // 499
+	CLOUDCHARGESPR,              // 500
+	BOLT1SPR,               // 501
+	BOLT2SPR,               // 502
+	END_LUMP(THUNDERCLOUD_LUMP_END, __THUNDERCLOUDEND)
+
+	START_LUMP(BERKELOID_LUMP_START, __BERKELOIDSTART)
+	BERKEWALKL1SPR,              // 503
+	BERKEWALKL2SPR,              // 504
+	BERKEWALKL3SPR,              // 505
+	BERKEWALKL4SPR,              // 506
+	BERKEWALKR1SPR,              // 507
+	BERKEWALKR2SPR,              // 508
+	BERKEWALKR3SPR,              // 509
+	BERKEWALKR4SPR,              // 510
+	BERKETHROWL1SPR,             // 511
+	BERKETHROWL2SPR,             // 512
+	BERKETHROWR1SPR,             // 513
+	BERKETHROWR2SPR,             // 514
+	FIREBALL1SPR,                // 515
+	FIREBALL2SPR,                // 516
+	FIREBALL3SPR,                // 517
+	FIREBALL4SPR,                // 518
+	END_LUMP(BERKELOID_LUMP_END, __BERKELOIDEND)
+
+	START_LUMP(MOON_LUMP_START, __MOONSTART)
+	KEENMOON1SPR,                // 519
+	KEENMOON2SPR,                // 520
+	END_LUMP(MOON_LUMP_END, __MOONEND)
+
+	//
+	// TILES (these don't need names)
+	//
+
+	LASTTILE=STARTEXTERNS-1,
+
+	//
+	// EXTERNS
+	//
+
+	ORDERSCREEN,                 // 4735
+	BIGCOMMANDER,                // 4736
+	BIGKEEN,                     // 4737
+	OUTOFMEM,                    // 4738
+
+	//texts
+	T_HELPART,                   // 4739
+	T_STORYART,                  // 4740
+	T_CONTRART,                  // 4741
+	T_IDART,                     // 4742
+	T_ENDART,                    // 4743
+	T_DEMOART,                   // 4744
+	T_ORDERART,                  // 4745
+
+	//demos
+	DEMO0,                       // 4746
+	DEMO1,                       // 4747
+	DEMO2,                       // 4748
+	DEMO3,                       // 4749
+	DEMO4,                       // 4750
+
+	NUMGRCHUNKS
+} graphicnums;
+
+#undef START_LUMP
+#undef END_LUMP
+
+#endif //__GFX_H__
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/KEEN4C/ID_ASM.EQU b/16/keen456/KEEN4-6/KEEN4C/ID_ASM.EQU
new file mode 100755
index 00000000..2c3c92e3
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN4C/ID_ASM.EQU
@@ -0,0 +1,115 @@
+;
+; Equates for all .ASM files
+;
+
+;----------------------------------------------------------------------------
+
+INCLUDE	"GFXC_CK4.EQU"
+
+;----------------------------------------------------------------------------
+
+CGAGR		=	1
+EGAGR		=	2
+VGAGR		=	3
+
+GRMODE		=	CGAGR
+PROFILE		=	0			; 1=keep stats on tile drawing
+
+SC_INDEX	=	03C4h
+SC_RESET	=	0
+SC_CLOCK	=	1
+SC_MAPMASK	=	2
+SC_CHARMAP	=	3
+SC_MEMMODE	=	4
+
+CRTC_INDEX	=	03D4h
+CRTC_H_TOTAL	=	0
+CRTC_H_DISPEND	=	1
+CRTC_H_BLANK	=	2
+CRTC_H_ENDBLANK	=	3
+CRTC_H_RETRACE	=	4
+CRTC_H_ENDRETRACE =	5
+CRTC_V_TOTAL	=	6
+CRTC_OVERFLOW	=	7
+CRTC_ROWSCAN	=	8
+CRTC_MAXSCANLINE =	9
+CRTC_CURSORSTART =	10
+CRTC_CURSOREND	=	11
+CRTC_STARTHIGH	=	12
+CRTC_STARTLOW	=	13
+CRTC_CURSORHIGH	=	14
+CRTC_CURSORLOW	=	15
+CRTC_V_RETRACE	=	16
+CRTC_V_ENDRETRACE =	17
+CRTC_V_DISPEND	=	18
+CRTC_OFFSET	=	19
+CRTC_UNDERLINE	=	20
+CRTC_V_BLANK	=	21
+CRTC_V_ENDBLANK	=	22
+CRTC_MODE	=	23
+CRTC_LINECOMPARE =	24
+
+
+GC_INDEX	=	03CEh
+GC_SETRESET	=	0
+GC_ENABLESETRESET =	1
+GC_COLORCOMPARE	=	2
+GC_DATAROTATE	=	3
+GC_READMAP	=	4
+GC_MODE		=	5
+GC_MISCELLANEOUS =	6
+GC_COLORDONTCARE =	7
+GC_BITMASK	=	8
+
+ATR_INDEX	=	03c0h
+ATR_MODE	=	16
+ATR_OVERSCAN	=	17
+ATR_COLORPLANEENABLE =	18
+ATR_PELPAN	=	19
+ATR_COLORSELECT	=	20
+
+STATUS_REGISTER_1     =	03dah
+
+
+MACRO	WORDOUT
+	out	dx,ax
+ENDM
+
+if 0
+
+MACRO	WORDOUT
+	out	dx,al
+	inc	dx
+	xchg	al,ah
+	out	dx,al
+	dec	dx
+	xchg	al,ah
+ENDM
+
+endif
+
+UPDATEWIDE	=	22
+UPDATEHIGH	=	14
+
+;
+; tile info offsets from segment tinf
+;
+
+ANIM		=	402
+SPEED		=	(ANIM+NUMTILE16)
+
+NORTHWALL	=	(SPEED+NUMTILE16)
+EASTWALL	=	(NORTHWALL+NUMTILE16M)
+SOUTHWALL   =	(EASTWALL+NUMTILE16M)
+WESTWALL    =	(SOUTHWALL+NUMTILE16M)
+MANIM       =	(WESTWALL+NUMTILE16M)
+INTILE      =	(MANIM+NUMTILE16M)
+MSPEED      =	(INTILE+NUMTILE16M)
+
+
+IFE GRMODE-EGAGR
+SCREENWIDTH	=	64
+ENDIF
+IFE GRMODE-CGAGR
+SCREENWIDTH	=	128
+ENDIF
diff --git a/16/keen456/KEEN4-6/KEEN4C/ID_HEADS.H b/16/keen456/KEEN4-6/KEEN4C/ID_HEADS.H
new file mode 100755
index 00000000..a73a9264
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN4C/ID_HEADS.H
@@ -0,0 +1,109 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+// ID_GLOB.H
+
+
+#include <ALLOC.H>
+#include <CTYPE.H>
+#include <DOS.H>
+#include <ERRNO.H>
+#include <FCNTL.H>
+#include <IO.H>
+#include <MEM.H>
+#include <PROCESS.H>
+#include <STDIO.H>
+#include <STDLIB.H>
+#include <STRING.H>
+#include <SYS\STAT.H>
+
+#define __ID_GLOB__
+
+//--------------------------------------------------------------------------
+
+#define KEEN
+#define KEEN4
+
+#define	EXTENSION	"CK4"
+
+extern	char far introscn;
+
+#include "GFXC_CK4.H"
+#include "AUDIOCK4.H"
+
+//--------------------------------------------------------------------------
+
+#define	TEXTGR	0
+#define	CGAGR	1
+#define	EGAGR	2
+#define	VGAGR	3
+
+#define GRMODE	CGAGR
+
+#if GRMODE == EGAGR
+#define GREXT	"EGA"
+#endif
+#if GRMODE == CGAGR
+#define GREXT	"CGA"
+#endif
+
+//#define PROFILE
+
+//
+//	ID Engine
+//	Types.h - Generic types, #defines, etc.
+//	v1.0d1
+//
+
+#ifndef	__TYPES__
+#define	__TYPES__
+
+typedef	enum	{false,true}	boolean;
+typedef	unsigned	char		byte;
+typedef	unsigned	int			word;
+typedef	unsigned	long		longword;
+typedef	byte *					Ptr;
+
+typedef	struct
+		{
+			int	x,y;
+		} Point;
+typedef	struct
+		{
+			Point	ul,lr;
+		} Rect;
+
+#define	nil	((void *)0)
+
+#endif
+
+#include "ID_MM.H"
+#include "ID_CA.H"
+#include "ID_VW.H"
+#include "ID_RF.H"
+#include "ID_IN.H"
+#include "ID_SD.H"
+#include "ID_US.H"
+
+
+void	Quit (char *error);		// defined in user program
+
diff --git a/16/keen456/KEEN4-6/KEEN5/AUDIOCK5.H b/16/keen456/KEEN4-6/KEEN5/AUDIOCK5.H
new file mode 100755
index 00000000..d7710a07
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN5/AUDIOCK5.H
@@ -0,0 +1,145 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+#ifndef __AUDIO_H__
+#define __AUDIO_H__
+
+//#include "VERSION.H"
+
+/////////////////////////////////////////////////
+//
+// MUSE Header for .CK5
+//
+/////////////////////////////////////////////////
+
+#define NUMSOUNDS     LASTSOUND
+#define NUMSNDCHUNKS  ((3*LASTSOUND)+LASTMUSIC)
+
+//
+// Sound names & indexes
+//
+typedef enum {
+	SND_WORLDWALK1,        // 0
+	SND_WORLDWALK2,        // 1
+	SND_JUMP,              // 2
+	SND_LAND,              // 3
+	SND_KEENFIRE,          // 4
+	SND_MINEEXPLODE,       // 5
+	SND_SLICESTARBOUNCE,   // 6
+	SND_POGOBOUNCE,        // 7
+	SND_GETPOINTS,         // 8
+	SND_GETAMMO,           // 9
+	SND_GETWATER,          // 10
+	SND_11,                // 11
+	SND_ENTERLEVEL,        // 12
+	SND_LEVELDONE,         // 13
+	SND_NOWAY,             // 14
+	SND_HELMETHIT,         // 15
+	SND_BOUNCE,            // 16
+	SND_EXTRAKEEN,         // 17
+	SND_OPENCARDDOOR,      // 18
+	SND_GETKEY,            // 19
+	SND_PLUMMET,           // 20
+	SND_USESWITCH,         // 21
+	SND_22,                // 22
+	SND_KEENDEAD,          // 23
+	SND_24,                // 24
+	SND_SHOTEXPLODE,       // 25
+	SND_26,                // 26
+	SND_SPIROGRAB,         // 27
+	SND_SPINDREDBOUNCE,    // 28
+	SND_ENEMYSHOT,         // 29
+	SND_ENEMYSHOTEXPLODE,  // 30
+	SND_AMPTONWALK1,       // 31
+	SND_AMPTONWALK2,       // 32
+	SND_AMPTONDIE,         // 33
+	SND_SHOWSTATUS,        // 34
+	SND_HIDESTATUS,        // 35
+	SND_SHELLEYEXPLODE,    // 36
+	SND_SPINDREDFLIP,      // 37
+	SND_MASTERATTACK,      // 38
+	SND_MASTERBLAST,       // 39
+	SND_SHIKADIATTACK,     // 40
+	SND_TELEPORT,          // 41
+	SND_SHOCKSHUNDBARK,    // 42
+	SND_FLAGSPIN,          // 43
+	SND_FLAGLAND,          // 44
+	SND_SHOCKBALLEXPLODE,  // 45
+	KEENPADDLESND,         // 46
+	BALLBOUNCESND,         // 47
+	COMPPADDLESND,         // 48
+	COMPSCOREDSND,         // 49
+	KEENSCOREDSND,         // 50
+	SND_51,                // 51
+	SND_BIGSPARK,          // 52
+	SND_GAMEOVER1,         // 53
+	SND_GAMEOVER2,         // 54
+	SND_GETKEYCARD,        // 55
+	SND_56,                // 56
+	SND_LANDONFUSE,        // 57
+	SND_SPARKYCHARGE,      // 58
+	SND_SPHEREFULBOUNCE,   // 59
+	SND_OPENDOOR,          // 60
+	SND_SPIROFLY,          // 61
+	SND_62,                // 62
+	SND_ELEVATORDOOR,      // 63
+	LASTSOUND
+} soundnames;
+
+#if LASTSOUND != 64
+#error bad sound enum!
+#endif
+
+#define NOWAYSND SND_NOWAY
+
+//
+// Base offsets
+//
+#define STARTPCSOUNDS     0
+#define STARTADLIBSOUNDS  (STARTPCSOUNDS+NUMSOUNDS)
+#define STARTDIGISOUNDS   (STARTADLIBSOUNDS+NUMSOUNDS)
+#define STARTMUSIC        (STARTDIGISOUNDS+NUMSOUNDS)
+
+//
+// Music names & indexes
+//
+typedef enum {
+	CAMEIN_MUS,
+	HAVING_T_MUS,
+	SKATING_MUS,
+	SNOOPING_MUS,
+	BAGPIPES_MUS,
+	WEDNESDY_MUS,
+	ROCK_ME_MUS,
+	BREATHE_MUS,
+	SHIKAIRE_MUS,
+	SPHEREFUL_MUS,
+	TIGHTER_MUS,
+	ROBOROCK_MUS,
+	FANFARE_MUS,
+	FEARSOME_MUS,
+	LASTMUSIC
+} musicnames;
+
+/////////////////////////////////////////////////
+//
+// Thanks for playing with MUSE!
+//
+/////////////////////////////////////////////////
+
+#endif
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/KEEN5/GFXE_CK5.EQU b/16/keen456/KEEN4-6/KEEN5/GFXE_CK5.EQU
new file mode 100755
index 00000000..11237984
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN5/GFXE_CK5.EQU
@@ -0,0 +1,55 @@
+;=====================================
+;
+; Graphics .EQU file for .CK5
+; not IGRAB-ed :)
+;
+;=====================================
+
+;INCLUDE "VERSION.EQU"
+
+;
+; Amount of each data item
+;
+NUMFONT     =	3
+NUMFONTM    =	0
+NUMPICM     =	3
+NUMTILE8    =	108
+NUMTILE8M   =	36
+NUMTILE32   =	0
+NUMTILE32M  =	0
+
+;
+; Amount of each item in episode 5
+;
+NUMPICS     =	93
+NUMSPRITES  =	346
+NUMTILE16   =	1512
+NUMTILE16M  =	2952
+NUMEXTERN   =	15
+
+
+;
+; File offsets for data items
+;
+STRUCTPIC       =	0
+STRUCTPICM      =	1
+STRUCTSPRITE    =	2
+
+STARTFONT       =	3
+STARTFONTM      =	(STARTFONT+NUMFONT)
+STARTPICS       =	(STARTFONTM+NUMFONTM)
+STARTPICM       =	(STARTPICS+NUMPICS)
+STARTSPRITES    =	(STARTPICM+NUMPICM)
+STARTTILE8      =	(STARTSPRITES+NUMSPRITES)
+STARTTILE8M     =	(STARTTILE8+1)
+STARTTILE16     =	(STARTTILE8M+1)
+STARTTILE16M    =	(STARTTILE16+NUMTILE16)
+STARTTILE32     =	(STARTTILE16M+NUMTILE16M)
+STARTTILE32M    =	(STARTTILE32+NUMTILE32)
+STARTEXTERN     =	(STARTTILE32M+NUMTILE32M)
+
+NUMCHUNKS       =	(STARTEXTERN+NUMEXTERN)
+
+;
+; Thank you for using IGRAB!
+;
diff --git a/16/keen456/KEEN4-6/KEEN5/GFXE_CK5.H b/16/keen456/KEEN4-6/KEEN5/GFXE_CK5.H
new file mode 100755
index 00000000..f35848c9
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN5/GFXE_CK5.H
@@ -0,0 +1,690 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+#ifndef __GFX_H__
+#define __GFX_H__
+
+//#include "VERSION.H"
+
+//////////////////////////////////////
+//
+// Graphics .H file for .CK5
+// not IGRAB-ed :)
+//
+//////////////////////////////////////
+
+//
+// Lump creation macros
+//
+
+#define START_LUMP(actualname, dummyname) actualname, dummyname=actualname-1,
+#define END_LUMP(actualname, dummyname) dummyname, actualname=dummyname-1,
+
+//
+// Amount of each data item
+//
+
+//common numbers:
+#define NUMCHUNKS    NUMGRCHUNKS
+#define NUMFONT      3
+#define NUMFONTM     0
+#define NUMPICM      3
+#define NUMTILE8     108	// BUG: only 104 tiles exist in EGAGRAPH!
+#define NUMTILE8M    36		// BUG: only 20 tiles exist in EGAGRAPH!
+#define NUMTILE32    0
+#define NUMTILE32M   0
+
+//episode-specific numbers:
+#define NUMPICS      93
+#define NUMSPRITES   346
+#define NUMTILE16    1512
+#define NUMTILE16M   2952
+#define NUMEXTERNS   17
+
+//
+// File offsets for data items
+//
+#define STRUCTPIC    0
+#define STRUCTPICM   1
+#define STRUCTSPRITE 2
+
+#define STARTFONT    3
+#define STARTFONTM   (STARTFONT+NUMFONT)
+#define STARTPICS    (STARTFONTM+NUMFONTM)
+#define STARTPICM    (STARTPICS+NUMPICS)
+#define STARTSPRITES (STARTPICM+NUMPICM)
+#define STARTTILE8   (STARTSPRITES+NUMSPRITES)
+#define STARTTILE8M  (STARTTILE8+1)
+#define STARTTILE16  (STARTTILE8M+1)
+#define STARTTILE16M (STARTTILE16+NUMTILE16)
+#define STARTTILE32  (STARTTILE16M+NUMTILE16M)
+#define STARTTILE32M (STARTTILE32+NUMTILE32)
+#define STARTEXTERNS (STARTTILE32M+NUMTILE32M)
+
+typedef enum {
+	// Lump Start
+
+	LASTFONT=STARTPICS-1,
+
+	START_LUMP(HELP_LUMP_START, __HELPSTART)
+	H_HELPPIC,                   // 6
+	H_LARROWPIC,                 // 7
+	H_RARROWPIC,                 // 8
+	H_ESCPIC,                    // 9
+	H_ENTERPIC,                  // 10
+	H_BOTTOMINSTRPIC,            // 11
+	H_GUMPIC,                    // 12
+	H_MARSHMALLOWPIC,            // 13
+	H_CHOCMILKPIC,               // 14
+	H_TARTSTIXPIC,               // 15
+	H_STOOPIESPIC,               // 16
+	H_SUGARPIC,                  // 17
+	H_VITALINPIC,                // 18
+	H_STUNNERPIC,                // 19
+	H_GEMPIC,                    // 20
+	H_KEGPIC,                    // 21
+	H_ENDOFTEXTPIC,              // 22
+	H_HELPMENUPIC,               // 23
+	H_HANDPIC,                   // 24
+	H_ARROWSENTERESCPIC,         // 25
+	H_FLASHARROW1PIC,            // 26
+	H_FLASHARROW2PIC,            // 27
+	H_TOPWINDOWPIC,              // 28
+	H_LEFTWINDOWPIC,             // 29
+	H_RIGHTWINDOWPIC,            // 30
+	H_BOTTOMINFOPIC,             // 31
+	H_BOTTOMWINDOWPIC,           // 32
+	H_BARPIC,                    // 33
+	H_SPARKYPIC,                 // 34
+	H_AMPTONPIC,                 // 35
+	H_SLICESTARPIC,              // 36
+	H_VOLTEFACEPIC,              // 37
+	H_ROBOREDPIC,                // 38
+	H_SHELLEYPIC,                // 39
+	H_SPIROGRIPPIC,              // 40
+	H_MINEPIC,                   // 41
+	H_SPINDREDPIC,               // 42
+	H_SHIKADIPIC,                // 43
+	H_SPHEREFULPIC,              // 44
+	H_PETPIC,                    // 45
+	H_MASTERPIC,                 // 46
+	H_IDLOGOPIC,                 // 47
+	H_STORY1PIC,                 // 48
+	H_STORY2PIC,                 // 49
+	H_STORY3PIC,                 // 50
+	H_STORY4PIC,                 // 51
+	H_VISAPIC,                   // 52
+	H_MCPIC,                     // 53
+	H_KEENTHUMBSUPPIC,           // 54
+	H_END1PIC,                   // 55
+	H_END2PIC,                   // 56
+	H_END3PIC,                   // 57
+	H_END4PIC,                   // 58
+	H_END5PIC,                   // 59
+	H_END6PIC,                   // 60
+	H_END7PIC,                   // 61
+	H_END8PIC,                   // 62
+	H_CONGRATSPIC,               // 63
+	H_KEENFEEDSPIC,              // 64
+	H_DOORCARDPIC,               // 65
+	H_KEEN6PIC,                  // 66
+	END_LUMP(HELP_LUMP_END, __HELPEND)
+
+	START_LUMP(CONTROLS_LUMP_START, __CONTROLSSTART)
+	CP_MAINMENUPIC,              // 67
+	CP_NEWGAMEMENUPIC,           // 68
+	CP_LOADMENUPIC,              // 69
+	CP_SAVEMENUPIC,              // 70
+	CP_CONFIGMENUPIC,            // 71
+	CP_SOUNDMENUPIC,             // 72
+	CP_MUSICMENUPIC,             // 73
+	CP_KEYBOARDMENUPIC,          // 74
+	CP_KEYMOVEMENTPIC,           // 75
+	CP_KEYBUTTONPIC,             // 76
+	CP_JOYSTICKMENUPIC,          // 77
+	CP_OPTIONSMENUPIC,           // 78
+	CP_PADDLEWARPIC,             // 79
+	CP_QUITPIC,                  // 80
+	CP_JOYSTICKPIC,              // 81
+	CP_MENUSCREENPIC,            // 82
+	END_LUMP(CONTROLS_LUMP_END, __COLTROLSEND)
+
+	START_LUMP(_LUMP_START, __START)
+	IDSOFTPIC,                   // 83
+	PROGTEAMPIC,                 // 84
+	ARTISTPIC,                   // 85
+	DIRECTORPIC,                 // 86
+	SW_BACKGROUNDPIC,            // 87
+	TITLEPICPIC,                 // 88
+	MILKYWAYPIC,                 // 89
+	END_LUMP(_LUMP_END, __END)
+
+	START_LUMP(KEENTALK_LUMP_START, __KEENTALKSTART)
+	KEENTALK1PIC,                // 90
+	KEENTALK2PIC,                // 91
+	END_LUMP(KEENTALK_LUMP_END, __KEENTALKEND)
+
+	START_LUMP(LOADING_LUMP_START, __LOADINGSTART)
+	KEENCOUNT1PIC,               // 92
+	KEENCOUNT2PIC,               // 93
+	KEENCOUNT3PIC,               // 94
+	KEENCOUNT4PIC,               // 95
+	KEENCOUNT5PIC,               // 96
+	KEENCOUNT6PIC,               // 97
+	END_LUMP(LOADING_LUMP_END, __LOADINGEND)
+
+	GAMEOVERPIC,                 // 98
+
+	CP_MENUMASKPICM,             // 99
+	CORDPICM,                    // 100
+	METALPOLEPICM,               // 101
+
+	//
+	// SPRITES
+	//
+
+	START_LUMP(PADDLE_LUMP_START, __PADDLESTART)
+	PADDLESPR,                   // 102
+	BALLSPR,                     // 103
+	BALL1PIXELTOTHERIGHTSPR,     // 104
+	BALL2PIXELSTOTHERIGHTSPR,    // 105
+	BALL3PIXELSTOTHERIGHTSPR,    // 106
+	END_LUMP(PADDLE_LUMP_END, __PADDLEEND)
+
+	DEMOPLAQUESPR,               // 107
+
+	START_LUMP(KEEN_LUMP_START, __KEENSTART)
+	KEENSTANDRSPR,               // 108
+	KEENRUNR1SPR,                // 109
+	KEENRUNR2SPR,                // 110
+	KEENRUNR3SPR,                // 111
+	KEENRUNR4SPR,                // 112
+	KEENJUMPR1SPR,               // 113
+	KEENJUMPR2SPR,               // 114
+	KEENJUMPR3SPR,               // 115
+	KEENSTANDLSPR,               // 116
+	KEENRUNL1SPR,                // 117
+	KEENRUNL2SPR,                // 118
+	KEENRUNL3SPR,                // 119
+	KEENRUNL4SPR,                // 120
+	KEENJUMPL1SPR,               // 121
+	KEENJUMPL2SPR,               // 122
+	KEENJUMPL3SPR,               // 123
+	KEENLOOKUSPR,                // 124
+	KEENWAITR1SPR,               // 125
+	KEENWAITR2SPR,               // 126
+	KEENWAITR3SPR,               // 127
+	KEENSITREAD1SPR,             // 128
+	KEENSITREAD2SPR,             // 129
+	KEENSITREAD3SPR,             // 130
+	KEENSITREAD4SPR,             // 131
+	KEENREAD1SPR,                // 132
+	KEENREAD2SPR,                // 133
+	KEENREAD3SPR,                // 134
+	KEENSTOPREAD1SPR,            // 135
+	KEENSTOPREAD2SPR,            // 136
+	KEENLOOKD1SPR,               // 137
+	KEENLOOKD2SPR,               // 138
+	KEENONPLATSPR,               // 139
+	KEENDIE1SPR,                 // 140
+	KEENDIE2SPR,                 // 141
+	KEENSTUNSPR,                 // 142
+	STUNSTARS1SPR,               // 143
+	STUNSTARS2SPR,               // 144
+	STUNSTARS3SPR,               // 145
+	KEENSHOOTLSPR,               // 146
+	KEENJLSHOOTLSPR,             // 147
+	KEENJSHOOTDSPR,              // 148
+	KEENJSHOOTUSPR,              // 149
+	KEENSHOOTUSPR,               // 150
+	KEENSHOOTRSPR,               // 151
+	KEENJRSHOOTRSPR,             // 152
+	STUN1SPR,                    // 153
+	STUN2SPR,                    // 154
+	STUN3SPR,                    // 155
+	STUN4SPR,                    // 156
+	STUNHIT1SPR,                 // 157
+	STUNHIT2SPR,                 // 158
+	KEENSHINNYR1SPR,             // 159
+	KEENSHINNYR2SPR,             // 160
+	KEENSHINNYR3SPR,             // 161
+	KEENSLIDED1SPR,              // 162
+	KEENSLIDED2SPR,              // 163
+	KEENSLIDED3SPR,              // 164
+	KEENSLIDED4SPR,              // 165
+	KEENSHINNYL1SPR,             // 166
+	KEENSHINNYL2SPR,             // 167
+	KEENSHINNYL3SPR,             // 168
+	KEENPLSHOOTUSPR,             // 169
+	KEENPRSHOOTUSPR,             // 170
+	KEENPRSHOOTDSPR,             // 171
+	KEENPLSHOOTDSPR,             // 172
+	KEENPSHOOTLSPR,              // 173
+	KEENPSHOOTRSPR,              // 174
+	KEENENTER1SPR,               // 175
+	KEENENTER2SPR,               // 176
+	KEENENTER3SPR,               // 177
+	KEENENTER4SPR,               // 178
+	KEENENTER5SPR,               // 179
+	KEENHANGLSPR,                // 180
+	KEENHANGRSPR,                // 181
+	KEENCLIMBEDGEL1SPR,          // 182
+	KEENCLIMBEDGEL2SPR,          // 183
+	KEENCLIMBEDGEL3SPR,          // 184
+	KEENCLIMBEDGEL4SPR,          // 185
+	KEENCLIMBEDGER1SPR,          // 186
+	KEENCLIMBEDGER2SPR,          // 187
+	KEENCLIMBEDGER3SPR,          // 188
+	KEENCLIMBEDGER4SPR,          // 189
+	KEENPOGOR1SPR,               // 190
+	KEENPOGOR2SPR,               // 191
+	KEENPOGOL1SPR,               // 192
+	KEENPOGOL2SPR,               // 193
+	BONUS100UPSPR,               // 194
+	BONUS100SPR,                 // 195
+	BONUS200SPR,                 // 196
+	BONUS500SPR,                 // 197
+	BONUS1000SPR,                // 198
+	BONUS2000SPR,                // 199
+	BONUS5000SPR,                // 200
+	BONUS1UPSPR,                 // 201
+	BONUSCLIPSPR,                // 202
+	VIVAPOOF1SPR,                // 203
+	VIVAPOOF2SPR,                // 204
+	VIVAPOOF3SPR,                // 205
+	VIVAPOOF4SPR,                // 206
+	END_LUMP(KEEN_LUMP_END, __KEENEND)
+
+	START_LUMP(KEYCARD_LUMP_START, __KEYCARDSTART)
+	DOORCARD1SPR,                // 207
+	DOORCARD2SPR,                // 208
+	BONUSCARDSPR,                // 209
+	END_LUMP(KEYCARD_LUMP_END, __KEYCARDEND)
+
+	START_LUMP(SUGAR1_LUMP_START, __SUGAR1START)
+	SUGAR1ASPR,                  // 210
+	SUGAR1BSPR,                  // 211
+	END_LUMP(SUGAR1_LUMP_END, __SUGAR1END)
+
+	START_LUMP(SUGAR2_LUMP_START, __SUGAR2START)
+	SUGAR2ASPR,                  // 212
+	SUGAR2BSPR,                  // 213
+	END_LUMP(SUGAR2_LUMP_END, __SUGAR2END)
+
+	START_LUMP(SUGAR3_LUMP_START, __SUGAR3START)
+	SUGAR3ASPR,                  // 214
+	SUGAR3BSPR,                  // 215
+	END_LUMP(SUGAR3_LUMP_END, __SUGAR3END)
+
+	START_LUMP(SUGAR4_LUMP_START, __SUGAR4START)
+	SUGAR4ASPR,                  // 216
+	SUGAR4BSPR,                  // 217
+	END_LUMP(SUGAR4_LUMP_END, __SUGAR4END)
+
+	START_LUMP(SUGAR5_LUMP_START, __SUGAR5START)
+	SUGAR5ASPR,                  // 218
+	SUGAR5BSPR,                  // 219
+	END_LUMP(SUGAR5_LUMP_END, __SUGAR5END)
+
+	START_LUMP(SUGAR6_LUMP_START, __SUGAR6START)
+	SUGAR6ASPR,                  // 220
+	SUGAR6BSPR,                  // 221
+	END_LUMP(SUGAR6_LUMP_END, __SUGAR6END)
+
+	START_LUMP(ONEUP_LUMP_START, __ONEUPSTART)
+	ONEUPASPR,                   // 222
+	ONEUPBSPR,                   // 223
+	END_LUMP(ONEUP_LUMP_END, __ONEUPEND)
+
+	START_LUMP(KEYGEM_LUMP_START, __KEYGEMSTART)
+	REDGEM1SPR,                  // 224
+	REDGEM2SPR,                  // 225
+	YELLOWGEM1SPR,               // 226
+	YELLOWGEM2SPR,               // 227
+	BLUEGEM1SPR,                 // 228
+	BLUEGEM2SPR,                 // 229
+	GREENGEM1SPR,                // 230
+	GREENGEM2SPR,                // 231
+	BONUSGEMSPR,                 // 232
+	END_LUMP(KEYGEM_LUMP_END, __KEYGEMEND)
+
+	START_LUMP(AMMO_LUMP_START, __AMMOSTART)
+	STUNCLIP1SPR,                // 233
+	STUNCLIP2SPR,                // 234
+	END_LUMP(AMMO_LUMP_END, __AMMOEND)
+
+	SCOREBOXSPR,                 // 235
+
+	START_LUMP(LASER_LUMP_START, __LASERSTART)
+	LASER1SPR,                   // 236
+	LASER2SPR,                   // 237
+	LASER3SPR,                   // 238
+	LASER4SPR,                   // 239
+	LASERHIT1SPR,                // 240
+	LASERHIT2SPR,                // 241
+	END_LUMP(LASER_LUMP_END, __LASEREND)
+
+	START_LUMP(WORLDKEEN_LUMP_START, __WORLDKEENSTART)
+	WORLDKEENL1SPR,              // 242
+	WORLDKEENL2SPR,              // 243
+	WORLDKEENL3SPR,              // 244
+	WORLDKEENR1SPR,              // 245
+	WORLDKEENR2SPR,              // 246
+	WORLDKEENR3SPR,              // 247
+	WORLDKEENU1SPR,              // 248
+	WORLDKEENU2SPR,              // 249
+	WORLDKEENU3SPR,              // 250
+	WORLDKEEND1SPR,              // 251
+	WORLDKEEND2SPR,              // 252
+	WORLDKEEND3SPR,              // 253
+	WORLDKEENDR1SPR,             // 254
+	WORLDKEENDR2SPR,             // 255
+	WORLDKEENDR3SPR,             // 256
+	WORLDKEENDL1SPR,             // 257
+	WORLDKEENDL2SPR,             // 258
+	WORLDKEENDL3SPR,             // 259
+	WORLDKEENUL1SPR,             // 260
+	WORLDKEENUL2SPR,             // 261
+	WORLDKEENUL3SPR,             // 262
+	WORLDKEENUR1SPR,             // 263
+	WORLDKEENUR2SPR,             // 264
+	WORLDKEENUR3SPR,             // 265
+	WORLDKEENWAVE1SPR,           // 266
+	WORLDKEENWAVE2SPR,           // 267
+	FLAGFLIP1SPR,                // 268
+	FLAGFLIP2SPR,                // 269
+	FLAGFLIP3SPR,                // 270
+	FLAGFLIP4SPR,                // 271
+	FLAGFLIP5SPR,                // 272
+	FLAGFALL1SPR,                // 273
+	FLAGFALL2SPR,                // 274
+	FLAGFLAP1SPR,                // 275
+	FLAGFLAP2SPR,                // 276
+	FLAGFLAP3SPR,                // 277
+	FLAGFLAP4SPR,                // 278
+	SHOOTINGSTAR1SPR,            // 279
+	SHOOTINGSTAR2SPR,            // 280
+	WORLDTELSPARK1SPR,           // 281
+	WORLDTELSPARK2SPR,           // 282
+	END_LUMP(WORLDKEEN_LUMP_END, __WORLDKEENEND)
+
+	START_LUMP(FUSE_LUMP_START, __FUSESTART)
+	FUSEFLASH1SPR,               // 283
+	FUSEFLASH2SPR,               // 284
+	FUSEFLASH3SPR,               // 285
+	END_LUMP(FUSE_LUMP_END, __FUSEEND)
+
+	START_LUMP(STAREXPLODE_LUMP_START, __SMALLSPARKSTART)
+	STAREXPLODE1SPR,             // 286
+	STAREXPLODE2SPR,             // 287
+	STAREXPLODE3SPR,             // 288
+	STAREXPLODE4SPR,             // 289
+	END_LUMP(STAREXPLODE_LUMP_END, __SMALLSPARKEND)
+
+	START_LUMP(TELEPORT_LUMP_START, __TELEPORTSTART)
+	TELEPORTSPARK1SPR,           // 290
+	TELEPORTSPARK2SPR,           // 291
+	TELEPORTZAP1SPR,             // 292
+	TELEPORTZAP2SPR,             // 293
+	END_LUMP(TELEPORT_LUMP_END, __TELEPORTEND)
+
+	START_LUMP(SCOTTIE_LUMP_START, __KORATHSTART)
+	SCOTTIEWALKL1SPR,            // 294
+	SCOTTIEWALKL2SPR,            // 295
+	SCOTTIEWALKL3SPR,            // 296
+	SCOTTIEWALKL4SPR,            // 297
+	SCOTTIEWALKR1SPR,            // 298
+	SCOTTIEWALKR2SPR,            // 299
+	SCOTTIEWALKR3SPR,            // 300
+	SCOTTIEWALKR4SPR,            // 301
+	SCOTTIEFACESPR,              // 302
+	SCOTTIESTUNSPR,              // 303
+	END_LUMP(SCOTTIE_LUMP_END, __KORATHEND)
+
+	START_LUMP(MASTER_LUMP_START, __MASTERSTART)
+	MASTER1SPR,                  // 304
+	MASTER2SPR,                  // 305
+	MASTER3SPR,                  // 306
+	MASTER4SPR,                  // 307
+	MASTERTELEPORT1SPR,          // 308
+	MASTERTELEPORT2SPR,          // 309
+	SHIKMASTERCASTRSPR,          // 310
+	SHIKMASTERCASTLSPR,          // 311
+	MASTERFLOORSPARK1SPR,        // 312
+	MASTERFLOORSPARK2SPR,        // 313
+	MASTERFLOORSPARK3SPR,        // 314
+	MASTERFLOORSPARK4SPR,        // 315
+	MASTERSHOT1SPR,              // 316
+	MASTERSHOT2SPR,              // 317
+	MASTERSHOT3SPR,              // 318
+	MASTERSHOT4SPR,              // 319
+	END_LUMP(MASTER_LUMP_END, __MASTEREND)
+
+	START_LUMP(SHIKADI_LUMP_START, __SHIKADISTART)
+	SHIKADI1SPR,                 // 320
+	SHIKADI2SPR,                 // 321
+	SHIKADI3SPR,                 // 322
+	SHIKADI4SPR,                 // 323
+	SHIKADIGRABRSPR,             // 324
+	SHIKADIGRABLSPR,             // 325
+	SHIKADIPOLESPARK1SPR,        // 326
+	SHIKADIPOLESPARK2SPR,        // 327
+	SHIKADIWALKR1SPR,            // 328
+	SHIKADIWALKR2SPR,            // 329
+	SHIKADIWALKR3SPR,            // 330
+	SHIKADIWALKR4SPR,            // 331
+	SHIKADIWALKL1SPR,            // 332
+	SHIKADIWALKL2SPR,            // 333
+	SHIKADIWALKL3SPR,            // 334
+	SHIKADIWALKL4SPR,            // 335
+	SHIKADISTUNSPR,              // 336
+	END_LUMP(SHIKADI_LUMP_END, __SHIKADIEND)
+
+	START_LUMP(SHOCKSHUND_LUMP_START, __SHOCKSHUNDSTART)
+	PETSIT1SPR,                  // 337
+	PETSIT2SPR,                  // 338
+	PETRUNR1SPR,                 // 339
+	PETRUNR2SPR,                 // 340
+	PETRUNR3SPR,                 // 341
+	PETRUNR4SPR,                 // 342
+	PETRUNL1SPR,                 // 343
+	PETRUNL2SPR,                 // 344
+	PETRUNL3SPR,                 // 345
+	PETRUNL4SPR,                 // 346
+	PETJUMPLSPR,                 // 347
+	PETJUMPRSPR,                 // 348
+	PETBARKR1SPR,                // 349
+	PETBARKR2SPR,                // 350
+	PETBARKL1SPR,                // 351
+	PETBARKL2SPR,                // 352
+	PETSTUNSPR,                  // 353
+	PETSPARK1SPR,                // 354
+	PETSPARK2SPR,                // 355
+	PETSPARKHIT1SPR,             // 356
+	PETSPARKHIT2SPR,             // 357
+	END_LUMP(SHOCKSHUND_LUMP_END, __SHOCKSHUNDEND)
+
+	START_LUMP(SPHEREFUL_LUMP_START, __SPHEREFULSTART)
+	SPHEREFUL1SPR,               // 358
+	SPHEREFUL2SPR,               // 359
+	SPHEREFUL3SPR,               // 360
+	SPHEREFUL4SPR,               // 361
+	SPHEREGUARD1SPR,             // 362
+	SPHEREGUARD2SPR,             // 363
+	SPHEREGUARD3SPR,             // 364
+	SPHEREGUARD4SPR,             // 365
+	END_LUMP(SPHEREFUL_LUMP_END, __SPHEREFULEND)
+
+	START_LUMP(SPARKY_LUMP_START, __SPARKYSTART)
+	SPARKYWALKL1SPR,             // 366
+	SPARKYWALKL2SPR,             // 367
+	SPARKYWALKL3SPR,             // 368
+	SPARKYWALKL4SPR,             // 369
+	SPARKYTURN1SPR,              // 370
+	SPARKYTURN2SPR,              // 371
+	SPARKYTURN3SPR,              // 372
+	SPARKYWALKR1SPR,             // 373
+	SPARKYWALKR2SPR,             // 374
+	SPARKYWALKR3SPR,             // 375
+	SPARKYWALKR4SPR,             // 376
+	SPARKYSTUNSPR,               // 377
+	END_LUMP(SPARKY_LUMP_END, __SPARKYEND)
+
+	START_LUMP(MINE_LUMP_START, __MINESTART)
+	SHIKADIMINESPR,              // 378
+	SHIKADIMINEEYESPR,           // 379
+	SHIKADIMINEPULSE1SPR,        // 380
+	SHIKADIMINEPULSE2SPR,        // 381
+	SHIKADIMINEBOOM1SPR,         // 382
+	SHIKADIMINEBOOM2SPR,         // 383
+	SHIKADIMINEPIECESPR,         // 384
+	END_LUMP(MINE_LUMP_END, __MINEEND)
+
+	START_LUMP(SLICESTAR_LUMP_START, __SLICESTARSTART)
+	SLICESTARSPR,                // 385
+	SLICESTARBOOMSPR,            // 386
+	END_LUMP(SLICESTAR_LUMP_END, __SLICASTAREND)
+
+	START_LUMP(ROBORED_LUMP_START, __ROBOREDSTART)
+	ROBOREDRSPR,                 // 387
+	ROBOREDLSPR,                 // 388
+	ROBOSHOT1SPR,                // 389
+	ROBOSHOT2SPR,                // 390
+	ROBOSHOTHIT1SPR,             // 391
+	ROBOSHOTHIT2SPR,             // 392
+	END_LUMP(ROBORED_LUMP_END, __ROBOREDEND)
+
+	START_LUMP(SPIRO_LUMP_START, __SPIROSTART)
+	SPIROSITDSPR,                // 393
+	SPIROSITLSPR,                // 394
+	SPIROSITUSPR,                // 395
+	SPIROSITRSPR,                // 396
+	SPIROSPINULSPR,              // 397
+	SPIROSPINURSPR,              // 398
+	SPIROSPINDRSPR,              // 399
+	SPIROSPINDLSPR,              // 400
+	SPIROSPINDSPR,               // 401
+	SPIROSPINLSPR,               // 402
+	SPIROSPINUSPR,               // 403
+	SPIROSPINRSPR,               // 404
+	END_LUMP(SPIRO_LUMP_END, __SPIROEND)
+
+	START_LUMP(AMPTON_LUMP_START, __AMPTONSTART)
+	AMPTONWALKR1SPR,             // 405
+	AMPTONWALKR2SPR,             // 406
+	AMPTONWALKR3SPR,             // 407
+	AMPTONWALKR4SPR,             // 408
+	AMPTONFACESPR,               // 409
+	AMPTONGRAB1SPR,              // 410
+	AMPTONGRAB2SPR,              // 411
+	AMTONWALKL1SPR,              // 412
+	AMTONWALKL2SPR,              // 413
+	AMTONWALKL3SPR,              // 414
+	AMTONWALKL4SPR,              // 415
+	AMPTONSTUNSPR,               // 416
+	END_LUMP(AMPTON_LUMP_END, __AMPTONEND)
+
+	START_LUMP(VOLTE_LUMP_START, __VOLTESTART)
+	VOLTEFACE1SPR,               // 417
+	VOLTEFACE2SPR,               // 418
+	VOLTEFACE3SPR,               // 419
+	VOLTEFACE4SPR,               // 420
+	VOLTEFACESTUNSPR,            // 421
+	END_LUMP(VOLTE_LUMP_END, __VOLTEEND)
+
+	START_LUMP(SLOTPLAT_LUMP_START, __PINKPLATSTART)
+	SLOTPLAT1SPR,                // 422
+	SLOTPLAT2SPR,                // 423
+	END_LUMP(SLOTPLAT_LUMP_END, __PINKPLATEND)
+
+	START_LUMP(SPINDRED_LUMP_START, __SPINDREDSTART)
+	SPINDRED1SPR,                // 424
+	SPINDRED2SPR,                // 425
+	SPINDRED3SPR,                // 426
+	SPINDRED4SPR,                // 427
+	END_LUMP(SPINDRED_LUMP_END, __SPINDREDEND)
+
+	START_LUMP(SHELLEY_LUMP_START, __SHELLEYSTART)
+	SHELLEYR1SPR,                // 428
+	SHELLEYR2SPR,                // 429
+	SHELLEYR3SPR,                // 430
+	SHELLEYR4SPR,                // 431
+	SHELLEYL1SPR,                // 432
+	SHELLEYL2SPR,                // 433
+	SHELLEYL3SPR,                // 434
+	SHELLEYL4SPR,                // 435
+	SHELLEYJUMPRSPR,             // 436
+	SHELLEYFALLRSPR,             // 437
+	SHELLEYJUMPLSPR,             // 438
+	SHELLEYFALLLSPR,             // 439
+	SHELLEYBOOM1SPR,             // 440
+	SHELLEYBOOM2SPR,             // 441
+	SHELLEYBOOM3SPR,             // 442
+	SHELLEYBOOM4SPR,             // 443
+	SHELLEYPIECE1SPR,            // 444
+	SHELLEYPIECE2SPR,            // 445
+	END_LUMP(SHELLEY_LUMP_END, __SHELLEYEND)
+
+	START_LUMP(PLATFORM_LUMP_START, __PLATFORMSTART)
+	PLATFORMSPR,                 // 446
+	END_LUMP(PLATFORM_LUMP_END, __PLATFORMEND)
+
+	START_LUMP(MINIPLAT_LUMP_START, __MINIPLATSTART)
+	MINIPLATSPR,                // 447
+	END_LUMP(MINIPLAT_LUMP_END, __MINIPLATEND)
+
+
+	//
+	// TILES (these don't need names)
+	//
+
+	LASTTILE=STARTEXTERNS-1,
+
+	//
+	// EXTERNS
+	//
+
+	//texts
+	T_HELPART,                   // 4914
+	T_CONTRART,                  // 4915
+	T_STORYART,                  // 4916
+	T_IDART,                     // 4917
+	T_ENDART,                    // 4918
+	T_ENDART2,                   // 4919
+	T_ORDERART,                  // 4920
+
+	ORDERSCREEN,                 // 4921
+	BIGCOMMANDER,                // 4922
+	BIGKEEN,                     // 4923
+	OUTOFMEM,                    // 4924
+	GALAXY,                      // 4925
+
+	//demos
+	DEMO0,                       // 4926
+	DEMO1,                       // 4927
+	DEMO2,                       // 4928
+	DEMO3,                       // 4929
+	DEMO4,                       // 4930
+
+	NUMGRCHUNKS
+} graphicnums;
+
+#undef START_LUMP
+#undef END_LUMP
+
+#endif //__GFX_H__
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/KEEN5/ID_ASM.EQU b/16/keen456/KEEN4-6/KEEN5/ID_ASM.EQU
new file mode 100755
index 00000000..932d6f8b
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN5/ID_ASM.EQU
@@ -0,0 +1,115 @@
+;
+; Equates for all .ASM files
+;
+
+;----------------------------------------------------------------------------
+
+INCLUDE	"GFXE_CK5.EQU"
+
+;----------------------------------------------------------------------------
+
+CGAGR		=	1
+EGAGR		=	2
+VGAGR		=	3
+
+GRMODE		=	EGAGR
+PROFILE		=	0			; 1=keep stats on tile drawing
+
+SC_INDEX	=	03C4h
+SC_RESET	=	0
+SC_CLOCK	=	1
+SC_MAPMASK	=	2
+SC_CHARMAP	=	3
+SC_MEMMODE	=	4
+
+CRTC_INDEX	=	03D4h
+CRTC_H_TOTAL	=	0
+CRTC_H_DISPEND	=	1
+CRTC_H_BLANK	=	2
+CRTC_H_ENDBLANK	=	3
+CRTC_H_RETRACE	=	4
+CRTC_H_ENDRETRACE =	5
+CRTC_V_TOTAL	=	6
+CRTC_OVERFLOW	=	7
+CRTC_ROWSCAN	=	8
+CRTC_MAXSCANLINE =	9
+CRTC_CURSORSTART =	10
+CRTC_CURSOREND	=	11
+CRTC_STARTHIGH	=	12
+CRTC_STARTLOW	=	13
+CRTC_CURSORHIGH	=	14
+CRTC_CURSORLOW	=	15
+CRTC_V_RETRACE	=	16
+CRTC_V_ENDRETRACE =	17
+CRTC_V_DISPEND	=	18
+CRTC_OFFSET	=	19
+CRTC_UNDERLINE	=	20
+CRTC_V_BLANK	=	21
+CRTC_V_ENDBLANK	=	22
+CRTC_MODE	=	23
+CRTC_LINECOMPARE =	24
+
+
+GC_INDEX	=	03CEh
+GC_SETRESET	=	0
+GC_ENABLESETRESET =	1
+GC_COLORCOMPARE	=	2
+GC_DATAROTATE	=	3
+GC_READMAP	=	4
+GC_MODE		=	5
+GC_MISCELLANEOUS =	6
+GC_COLORDONTCARE =	7
+GC_BITMASK	=	8
+
+ATR_INDEX	=	03c0h
+ATR_MODE	=	16
+ATR_OVERSCAN	=	17
+ATR_COLORPLANEENABLE =	18
+ATR_PELPAN	=	19
+ATR_COLORSELECT	=	20
+
+STATUS_REGISTER_1     =	03dah
+
+
+MACRO	WORDOUT
+	out	dx,ax
+ENDM
+
+if 0
+
+MACRO	WORDOUT
+	out	dx,al
+	inc	dx
+	xchg	al,ah
+	out	dx,al
+	dec	dx
+	xchg	al,ah
+ENDM
+
+endif
+
+UPDATEWIDE	=	22
+UPDATEHIGH	=	14
+
+;
+; tile info offsets from segment tinf
+;
+
+ANIM		=	402
+SPEED		=	(ANIM+NUMTILE16)
+
+NORTHWALL	=	(SPEED+NUMTILE16)
+EASTWALL	=	(NORTHWALL+NUMTILE16M)
+SOUTHWALL   =	(EASTWALL+NUMTILE16M)
+WESTWALL    =	(SOUTHWALL+NUMTILE16M)
+MANIM       =	(WESTWALL+NUMTILE16M)
+INTILE      =	(MANIM+NUMTILE16M)
+MSPEED      =	(INTILE+NUMTILE16M)
+
+
+IFE GRMODE-EGAGR
+SCREENWIDTH	=	64
+ENDIF
+IFE GRMODE-CGAGR
+SCREENWIDTH	=	128
+ENDIF
diff --git a/16/keen456/KEEN4-6/KEEN5/ID_HEADS.H b/16/keen456/KEEN4-6/KEEN5/ID_HEADS.H
new file mode 100755
index 00000000..72b1b728
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN5/ID_HEADS.H
@@ -0,0 +1,109 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+// ID_GLOB.H
+
+
+#include <ALLOC.H>
+#include <CTYPE.H>
+#include <DOS.H>
+#include <ERRNO.H>
+#include <FCNTL.H>
+#include <IO.H>
+#include <MEM.H>
+#include <PROCESS.H>
+#include <STDIO.H>
+#include <STDLIB.H>
+#include <STRING.H>
+#include <SYS\STAT.H>
+
+#define __ID_GLOB__
+
+//--------------------------------------------------------------------------
+
+#define KEEN
+#define KEEN5
+
+#define	EXTENSION	"CK5"
+
+extern	char far introscn;
+
+#include "GFXE_CK5.H"
+#include "AUDIOCK5.H"
+
+//--------------------------------------------------------------------------
+
+#define	TEXTGR	0
+#define	CGAGR	1
+#define	EGAGR	2
+#define	VGAGR	3
+
+#define GRMODE	EGAGR
+
+#if GRMODE == EGAGR
+#define GREXT	"EGA"
+#endif
+#if GRMODE == CGAGR
+#define GREXT	"CGA"
+#endif
+
+//#define PROFILE
+
+//
+//	ID Engine
+//	Types.h - Generic types, #defines, etc.
+//	v1.0d1
+//
+
+#ifndef	__TYPES__
+#define	__TYPES__
+
+typedef	enum	{false,true}	boolean;
+typedef	unsigned	char		byte;
+typedef	unsigned	int			word;
+typedef	unsigned	long		longword;
+typedef	byte *					Ptr;
+
+typedef	struct
+		{
+			int	x,y;
+		} Point;
+typedef	struct
+		{
+			Point	ul,lr;
+		} Rect;
+
+#define	nil	((void *)0)
+
+#endif
+
+#include "ID_MM.H"
+#include "ID_CA.H"
+#include "ID_VW.H"
+#include "ID_RF.H"
+#include "ID_IN.H"
+#include "ID_SD.H"
+#include "ID_US.H"
+
+
+void	Quit (char *error);		// defined in user program
+
diff --git a/16/keen456/KEEN4-6/KEEN5/K5_ACT1.C b/16/keen456/KEEN4-6/KEEN5/K5_ACT1.C
new file mode 100755
index 00000000..9157bac9
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN5/K5_ACT1.C
@@ -0,0 +1,1524 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+/*
+K5_ACT1.C
+=========
+
+Contains the following actor types (in this order):
+
+- some shared routines
+- Bonus Items
+- Teleport and Fuse effects
+- Platforms
+- falling platforms
+- static platforms
+- Goplat platforms
+- Volte Face
+- sneaky platforms
+- Turrets
+
+*/
+
+#include "CK_DEF.H"
+
+/*
+=============================================================================
+
+						  SHARED STUFF
+
+=============================================================================
+*/
+
+Sint16 pdirx[] = {0, 1, 0, -1, 1, 1, -1, -1};
+Sint16 pdiry[] = {-1, 0, 1, 0, -1, 1, 1, -1};
+
+/*
+===========================
+=
+= CheckSpawnShot
+=
+===========================
+*/
+
+Sint16 CheckSpawnShot(Uint16 x, Uint16 y, statetype *state)
+{
+	if (GetNewObj(true) == -1)
+		return -1;
+	new->x = x;
+	new->y = y;
+	new->obclass = mshotobj;
+	new->active = ac_removable;
+	NewState(new, state);
+	if (!CheckPosition(new))
+	{
+		RemoveObj(new);
+		return -1;
+	}
+	return 0;
+}
+
+/*
+===========================
+=
+= C_ClipSide
+=
+===========================
+*/
+
+void C_ClipSide(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		playerkludgeclipcancel = true;
+		ClipToSpriteSide(hit, ob);
+		playerkludgeclipcancel = false;
+	}
+}
+
+/*
+===========================
+=
+= C_ClipTop
+=
+===========================
+*/
+
+void C_ClipTop(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+		ClipToSpriteTop(hit, ob);
+}
+
+/*
+===========================
+=
+= R_Land
+=
+===========================
+*/
+
+void R_Land(objtype *ob)
+{
+	if (ob->hiteast || ob->hitwest)
+		ob->xspeed = 0;
+
+	if (ob->hitsouth)
+		ob->yspeed = 0;
+
+	if (ob->hitnorth)
+	{
+		ob->yspeed = 0;
+		if (ob->state->nextstate)
+		{
+			ChangeState(ob, ob->state->nextstate);
+		}
+		else
+		{
+			RemoveObj(ob);
+			return;
+		}
+	}
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+===========================
+=
+= R_Bounce
+=
+===========================
+*/
+
+void R_Bounce(objtype *ob)
+{
+	Uint16 wall,absx,absy,angle,newangle;
+	Uint32 speed;
+
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+
+	if (ob->hiteast || ob->hitwest)
+		ob->xspeed = -ob->xspeed/2;
+
+	if (ob->hitsouth)
+	{
+		ob->yspeed = -ob->yspeed/2;
+		return;
+	}
+
+	wall = ob->hitnorth;
+	if (wall)
+	{
+		if (ob->yspeed < 0)
+			ob->yspeed = 0;
+
+		absx = abs(ob->xspeed);
+		absy = ob->yspeed;
+		if (absx>absy)
+		{
+			if (absx>absy*2)	// 22 degrees
+			{
+				angle = 0;
+				speed = absx*286;	// x*sqrt(5)/2
+			}
+			else				// 45 degrees
+			{
+				angle = 1;
+				speed = absx*362;	// x*sqrt(2)
+			}
+		}
+		else
+		{
+			if (absy>absx*2)	// 90 degrees
+			{
+				angle = 3;
+				speed = absy*256;
+			}
+			else
+			{
+				angle = 2;		// 67 degrees
+				speed = absy*286;	// y*sqrt(5)/2
+			}
+		}
+		if (ob->xspeed > 0)
+			angle = 7-angle;
+
+		speed >>= 1;
+		newangle = bounceangle[ob->hitnorth][angle];
+		switch (newangle)
+		{
+		case 0:
+			ob->xspeed = speed / 286;
+			ob->yspeed = -ob->xspeed / 2;
+			break;
+		case 1:
+			ob->xspeed = speed / 362;
+			ob->yspeed = -ob->xspeed;
+			break;
+		case 2:
+			ob->yspeed = -(speed / 286);
+			ob->xspeed = -ob->yspeed / 2;
+			break;
+		case 3:
+
+		case 4:
+			ob->xspeed = 0;
+			ob->yspeed = -(speed / 256);
+			break;
+		case 5:
+			ob->yspeed = -(speed / 286);
+			ob->xspeed = ob->yspeed / 2;
+			break;
+		case 6:
+			ob->xspeed = ob->yspeed = -(speed / 362);
+			break;
+		case 7:
+			ob->xspeed = -(speed / 286);
+			ob->yspeed = ob->xspeed / 2;
+			break;
+
+		case 8:
+			ob->xspeed = -(speed / 286);
+			ob->yspeed = -ob->xspeed / 2;
+			break;
+		case 9:
+			ob->xspeed = -(speed / 362);
+			ob->yspeed = -ob->xspeed;
+			break;
+		case 10:
+			ob->yspeed = speed / 286;
+			ob->xspeed = -ob->yspeed / 2;
+			break;
+		case 11:
+
+		case 12:
+			ob->xspeed = 0;
+			ob->yspeed = -(speed / 256);
+			break;
+		case 13:
+			ob->yspeed = speed / 286;
+			ob->xspeed = ob->yspeed / 2;
+			break;
+		case 14:
+			ob->xspeed = speed / 362;
+			ob->yspeed = speed / 362;
+			break;
+		case 15:
+			ob->xspeed = speed / 286;
+			ob->yspeed = ob->xspeed / 2;
+			break;
+		}
+
+		if (speed < 256*16)
+		{
+			ChangeState(ob, ob->state->nextstate);
+		}
+	}
+}
+
+/*
+=============================================================================
+
+						  BONUS ITEMS
+temp1 = bonus type
+temp2 = base shape number
+temp3 = last animated shape number +1
+
+=============================================================================
+*/
+
+statetype s_bonus1    = {0,            0,            step,      false, false, 20, 0, 0, T_Bonus, NULL, R_Draw, &s_bonus2};
+statetype s_bonus2    = {0,            0,            step,      false, false, 20, 0, 0, T_Bonus, NULL, R_Draw, &s_bonus1};
+statetype s_bonusfly1 = {0,            0,            stepthink, false, false, 20, 0, 0, T_FlyBonus, NULL, R_Draw, &s_bonusfly2};
+statetype s_bonusfly2 = {0,            0,            stepthink, false, false, 20, 0, 0, T_FlyBonus, NULL, R_Draw, &s_bonusfly1};
+statetype s_bonusrise = {0,            0,            slide,     false, false, 40, 0, 8, NULL, NULL, R_Draw, NULL};
+statetype s_splash1   = {VIVAPOOF1SPR, VIVAPOOF1SPR, step,      false, false,  8, 0, 0, NULL, NULL, R_Draw, &s_splash2};
+statetype s_splash2   = {VIVAPOOF2SPR, VIVAPOOF2SPR, step,      false, false,  8, 0, 0, NULL, NULL, R_Draw, &s_splash3};
+statetype s_splash3   = {VIVAPOOF3SPR, VIVAPOOF3SPR, step,      false, false,  8, 0, 0, NULL, NULL, R_Draw, &s_splash4};
+statetype s_splash4   = {VIVAPOOF4SPR, VIVAPOOF4SPR, step,      false, false,  8, 0, 0, NULL, NULL, R_Draw, NULL};
+
+Uint16 bonusshape[] = {
+	REDGEM1SPR, YELLOWGEM1SPR, BLUEGEM1SPR, GREENGEM1SPR,
+	SUGAR1ASPR, SUGAR2ASPR, SUGAR3ASPR,
+	SUGAR4ASPR, SUGAR5ASPR, SUGAR6ASPR,
+	ONEUPASPR, STUNCLIP1SPR, DOORCARD1SPR
+};
+
+/*
+===========================
+=
+= SpawnBonus
+=
+===========================
+*/
+
+void SpawnBonus(Uint16 tileX, Uint16 tileY, Uint16 type)
+{
+	GetNewObj(false);
+	new->needtoclip = cl_noclip;
+	new->priority = 2;
+	new->obclass = bonusobj;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	new->ydir = -1;
+	new->temp1 = type;
+	new->temp2=new->shapenum = bonusshape[type];
+	new->temp3 = new->temp2+2;
+	NewState(new, &s_bonus1);
+}
+
+/*
+===========================
+=
+= SpawnSplash
+=
+===========================
+*/
+
+void SpawnSplash(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(true);
+	new->needtoclip = cl_noclip;
+	new->priority = 3;
+	new->obclass = inertobj;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	NewState(new, &s_splash1);
+}
+
+/*
+===========================
+=
+= T_Bonus
+=
+===========================
+*/
+
+void T_Bonus(objtype *ob)
+{
+	if (++ob->shapenum == ob->temp3)
+		ob->shapenum = ob->temp2;
+}
+
+/*
+===========================
+=
+= T_FlyBonus
+=
+===========================
+*/
+
+void T_FlyBonus(objtype *ob)
+{
+	if (ob->hitnorth)
+		ob->state = &s_bonus1;
+
+	if (++ob->shapenum == ob->temp3)
+		ob->shapenum = ob->temp2;
+
+	DoGravity(ob);
+}
+
+/*
+=============================================================================
+
+						  TELEPORT EFFECTS
+
+=============================================================================
+*/
+
+statetype s_teleport1     = {TELEPORTSPARK1SPR, TELEPORTSPARK1SPR, step, false, false, 6, 0, 0, NULL, NULL, R_Draw, &s_teleport2};
+statetype s_teleport2     = {TELEPORTSPARK2SPR, TELEPORTSPARK2SPR, step, false, false, 6, 0, 0, NULL, NULL, R_Draw, &s_teleport1};
+statetype s_teleportzap1  = {TELEPORTZAP1SPR,   TELEPORTZAP1SPR,   step, false, false, 6, 0, 0, NULL, NULL, R_Draw, &s_teleportzap2};
+statetype s_teleportzap2  = {TELEPORTZAP2SPR,   TELEPORTZAP2SPR,   step, false, false, 6, 0, 0, NULL, NULL, R_Draw, &s_teleportzap1};
+
+/*
+===========================
+=
+= SpawnTeleport
+=
+===========================
+*/
+
+void SpawnTeleport(void)
+{
+	GetNewObj(true);
+	new->priority = 3;
+	new->needtoclip = cl_noclip;
+	new->obclass = teleporterobj;
+	new->x = CONVERT_TILE_TO_GLOBAL(player->tileleft) - 8*PIXGLOBAL;
+	new->y = CONVERT_TILE_TO_GLOBAL(player->tilebottom) - 5*TILEGLOBAL;
+	NewState(new, &s_teleport1);
+
+	GetNewObj(true);
+	new->priority = 3;
+	new->needtoclip = cl_noclip;
+	new->obclass = teleporterobj;
+	new->x = CONVERT_TILE_TO_GLOBAL(player->tileleft);
+	new->y = CONVERT_TILE_TO_GLOBAL(player->tiletop) - 8*PIXGLOBAL;
+	NewState(new, &s_teleportzap1);
+
+	SD_PlaySound(SND_TELEPORT);
+}
+
+/*
+=============================================================================
+
+						  FUSE FLASH
+
+=============================================================================
+*/
+
+statetype s_fuseflash1    = {FUSEFLASH1SPR, FUSEFLASH1SPR, step, false, false, 10, 0, 0, NULL, NULL, R_Draw, &s_fuseflash2};
+statetype s_fuseflash2    = {FUSEFLASH2SPR, FUSEFLASH2SPR, step, false, false, 20, 0, 0, NULL, NULL, R_Draw, &s_fuseflash3};
+statetype s_fuseflash3    = {FUSEFLASH3SPR, FUSEFLASH3SPR, step, false, false, 10, 0, 0, NULL, NULL, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnFuseFlash
+=
+===========================
+*/
+
+void SpawnFuseFlash(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(true);
+	new->priority = 3;
+	new->needtoclip = cl_noclip;
+	new->obclass = teleporterobj;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX-1);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	NewState(new, &s_fuseflash1);
+	SD_PlaySound(SND_BIGSPARK);
+}
+
+/*
+=============================================================================
+
+						  DEAD MACHINE
+
+=============================================================================
+*/
+
+statetype s_deadmachine   = {-1, -1, step, false, false, 60, 0, 0, T_DeadMachine, NULL, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnDeadMachine
+=
+===========================
+*/
+
+void SpawnDeadMachine(void)
+{
+	GetNewObj(false);
+	new->active = ac_allways;
+	new->needtoclip = cl_noclip;
+	NewState(new, &s_deadmachine);
+}
+
+/*
+===========================
+=
+= T_DeadMachine
+=
+===========================
+*/
+
+#pragma argsused
+void T_DeadMachine(objtype *ob)
+{
+	if (mapon == 12)
+	{
+		playstate = ex_qedbroke;
+	}
+	else
+	{
+		playstate = ex_fusebroke;
+	}
+}
+
+/*
+=============================================================================
+
+						  PLATFORMS
+
+=============================================================================
+*/
+
+statetype s_platform      = {PLATFORMSPR,  PLATFORMSPR,  think,     false, false, 0, 0, 0, T_Platform, NULL, R_Draw, NULL};
+statetype s_slotplat1     = {SLOTPLAT1SPR, SLOTPLAT1SPR, stepthink, false, false, 0, 0, 0, T_Slotplat, NULL, R_Draw, &s_slotplat2};
+statetype s_slotplat2     = {SLOTPLAT2SPR, SLOTPLAT2SPR, stepthink, false, false, 0, 0, 0, T_Slotplat, NULL, R_Draw, &s_slotplat1};
+// BUG? the slotplat states have a tictime of 0, so they never transition to the next state
+
+/*
+===========================
+=
+= SpawnPlatform
+=
+===========================
+*/
+
+void SpawnPlatform(Uint16 tileX, Uint16 tileY, Sint16 dir, Sint16 type)
+{
+	GetNewObj(false);
+	new->obclass = platformobj;
+	new->active = ac_allways;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	switch (dir)
+	{
+	case 0:
+		new->xdir = 0;
+		new->ydir = -1;
+		break;
+	case 1:
+		new->xdir = 1;
+		new->ydir = 0;
+		break;
+	case 2:
+		new->xdir = 0;
+		new->ydir = 1;
+		break;
+	case 3:
+		new->xdir = -1;
+		new->ydir = 0;
+	}
+	if (type)
+	{
+		new->x += 4*PIXGLOBAL;
+		new->y += 4*PIXGLOBAL;
+		NewState(new, &s_slotplat1);
+	}
+	else
+	{
+		NewState(new, &s_platform);
+	}
+}
+
+/*
+===========================
+=
+= T_Platform
+=
+===========================
+*/
+
+void T_Platform(objtype *ob)
+{
+	Uint16 newpos, newtile;
+
+	//
+	// this code could be executed twice during the same frame because the
+	// object's animation/state changed during that frame, so don't update
+	// anything if we already have movement for the current frame i.e. the
+	// update code has already been executed this frame
+	//
+	if (!xtry && !ytry)
+	{
+		xtry = ob->xdir * 12 * tics;
+		ytry = ob->ydir * 12 * tics;
+
+		if (ob->xdir == 1)
+		{
+			newpos = ob->right + xtry;
+			newtile = CONVERT_GLOBAL_TO_TILE(newpos);
+			if (ob->tileright != newtile)
+			{
+				if (*(mapsegs[2]+mapbwidthtable[ob->tiletop]/2 + newtile) == PLATFORMBLOCK)
+				{
+					ob->xdir = -1;
+					xtry = xtry - (newpos & 0xFF);
+				}
+			}
+		}
+		else if (ob->xdir == -1)
+		{
+			newpos = ob->left + xtry;
+			newtile = CONVERT_GLOBAL_TO_TILE(newpos);
+			if (ob->tileleft != newtile)
+			{
+				if (*(mapsegs[2]+mapbwidthtable[ob->tiletop]/2 + newtile) == PLATFORMBLOCK)
+				{
+					ob->xdir = 1;
+					xtry = xtry + (TILEGLOBAL - (newpos & 0xFF));
+				}
+			}
+		}
+		else if (ob->ydir == 1)
+		{
+			newpos = ob->bottom + ytry;
+			newtile = CONVERT_GLOBAL_TO_TILE(newpos);
+			if (ob->tilebottom != newtile)
+			{
+				if (*(mapsegs[2]+mapbwidthtable[newtile]/2 + ob->tileleft) == PLATFORMBLOCK)
+				{
+					if (*(mapsegs[2]+mapbwidthtable[newtile-2]/2 + ob->tileleft) == PLATFORMBLOCK)
+					{
+						ytry = 0;
+						ob->needtoreact = true;
+					}
+					else
+					{
+						ob->ydir = -1;
+						ytry = ytry - (newpos & 0xFF);
+					}
+				}
+			}
+		}
+		else if (ob->ydir == -1)
+		{
+			newpos = ob->top + ytry;
+			newtile = CONVERT_GLOBAL_TO_TILE(newpos);
+			if (ob->tiletop != newtile)
+			{
+				if (*(mapsegs[2]+mapbwidthtable[newtile]/2 + ob->tileleft) == PLATFORMBLOCK)
+				{
+					if (*(mapsegs[2]+mapbwidthtable[newtile+2]/2 + ob->tileleft) == PLATFORMBLOCK)
+					{
+						ytry = 0;
+						ob->needtoreact = true;
+					}
+					else
+					{
+						ob->ydir = 1;
+						ytry = ytry + (TILEGLOBAL - (newpos & 0xFF));
+					}
+				}
+			}
+		}
+	}
+}
+
+/*
+===========================
+=
+= T_Slotplat
+=
+===========================
+*/
+
+void T_Slotplat(objtype *ob)
+{
+	Uint16 newpos, newtile;
+
+	//
+	// this code could be executed twice during the same frame because the
+	// object's animation/state changed during that frame, so don't update
+	// anything if we already have movement for the current frame i.e. the
+	// update code has already been executed this frame
+	//
+	if (!xtry && !ytry)
+	{
+		xtry = ob->xdir * 12 * tics;
+		ytry = ob->ydir * 12 * tics;
+
+		if (ob->xdir == 1)
+		{
+			newpos = ob->right + xtry;
+			newtile = CONVERT_GLOBAL_TO_TILE(newpos);
+			if (ob->tileright != newtile)
+			{
+				if (*(mapsegs[2]+mapbwidthtable[ob->tiletop]/2 + newtile) == PLATFORMBLOCK)
+				{
+					ob->xdir = -1;
+					xtry = xtry - (newpos & 0xFF);
+				}
+			}
+		}
+		else if (ob->xdir == -1)
+		{
+			newpos = ob->left + xtry;
+			newtile = CONVERT_GLOBAL_TO_TILE(newpos);
+			if (ob->tileleft != newtile)
+			{
+				if (*(mapsegs[2]+mapbwidthtable[ob->tiletop]/2 + newtile) == PLATFORMBLOCK)
+				{
+					ob->xdir = 1;
+					xtry = xtry + (TILEGLOBAL - (newpos & 0xFF));
+				}
+			}
+		}
+		else if (ob->ydir == 1)
+		{
+			newpos = ob->bottom + ytry;
+			newtile = CONVERT_GLOBAL_TO_TILE(newpos);
+			if (ob->tilebottom != newtile)
+			{
+				if (*(mapsegs[2]+mapbwidthtable[newtile]/2 + ob->tileleft + 1) == PLATFORMBLOCK)
+				{
+					if (*(mapsegs[2]+mapbwidthtable[newtile-2]/2 + ob->tileleft) == PLATFORMBLOCK)	// BUG? '+ 1' is missing after 'tileleft'
+					{
+						ytry = 0;
+						ob->needtoreact = true;
+					}
+					else
+					{
+						ob->ydir = -1;
+						ytry = ytry - (newpos & 0xFF);
+					}
+				}
+			}
+		}
+		else if (ob->ydir == -1)
+		{
+			newpos = ob->top + ytry;
+			newtile = CONVERT_GLOBAL_TO_TILE(newpos);
+			if (ob->tiletop != newtile)
+			{
+				if (*(mapsegs[2]+mapbwidthtable[newtile]/2 + ob->tileleft + 1) == PLATFORMBLOCK)
+				{
+					if (*(mapsegs[2]+mapbwidthtable[newtile+2]/2 + ob->tileleft + 1) == PLATFORMBLOCK)
+					{
+						ytry = 0;
+						ob->needtoreact = true;
+					}
+					else
+					{
+						ob->ydir = 1;
+						ytry = ytry + (TILEGLOBAL - (newpos & 0xFF));
+					}
+				}
+			}
+		}
+	}
+}
+
+/*
+=============================================================================
+
+						  DROPPING PLATFORM
+
+temp1 = initial y position
+
+=============================================================================
+*/
+
+statetype s_dropplatsit  = {PLATFORMSPR, PLATFORMSPR, think,      false, false, 0, 0,   0, T_DropPlatSit, NULL, R_Draw, NULL};
+statetype s_dropplatfall = {PLATFORMSPR, PLATFORMSPR, think,      false, false, 0, 0,   0, T_DropPlatFall, NULL, R_Draw, NULL};
+statetype s_dropplatrise = {PLATFORMSPR, PLATFORMSPR, slidethink, false, false, 0, 0, -32, T_DropPlatRise, NULL, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnDropPlat
+=
+===========================
+*/
+
+void SpawnDropPlat(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = platformobj;
+	new->active = ac_allways;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y=new->temp1 = CONVERT_TILE_TO_GLOBAL(tileY);
+	new->xdir = 0;
+	new->ydir = 1;
+	new->needtoclip = cl_noclip;
+	NewState(new, &s_dropplatsit);
+}
+
+/*
+===========================
+=
+= T_DropPlatSit
+=
+===========================
+*/
+
+void T_DropPlatSit(objtype *ob)
+{
+	if (gamestate.riding == ob)
+	{
+		ytry = tics << 4;	//tics * 16;
+		ob->yspeed = 0;
+		if (ob->y + ytry - ob->temp1 >= 8*PIXGLOBAL)
+			ob->state = &s_dropplatfall;
+	}
+}
+
+/*
+===========================
+=
+= T_DropPlatFall
+=
+===========================
+*/
+
+void T_DropPlatFall(objtype *ob)
+{
+	Uint16 newpos, newtile;
+
+	DoGravity(ob);
+
+#if 0
+	// bugfix: don't skip a tile (this is present in Keen 4, but missing in 5 & 6)
+	if (ytry >= 15*PIXGLOBAL)
+		ytry = 15*PIXGLOBAL;
+#endif
+
+	newpos = ob->bottom + ytry;
+	newtile = CONVERT_GLOBAL_TO_TILE(newpos);
+	if (ob->tilebottom != newtile)
+	{
+		if (*(mapsegs[2]+mapbwidthtable[newtile]/2 + ob->tileleft) == PLATFORMBLOCK)
+		{
+			ytry = 0xFF - (ob->bottom & 0xFF);
+			if (gamestate.riding != ob)
+				ob->state = &s_dropplatrise;
+		}
+	}
+}
+
+/*
+===========================
+=
+= T_DropPlatRise
+=
+===========================
+*/
+
+void T_DropPlatRise(objtype *ob)
+{
+	if (gamestate.riding == ob)
+	{
+		ob->yspeed = 0;
+		ob->state = &s_dropplatfall;
+	}
+	else if (ob->y <= ob->temp1)
+	{
+		ytry = ob->temp1 - ob->y;
+		ob->state = &s_dropplatsit;
+	}
+}
+
+/*
+=============================================================================
+
+						  STATIC PLATFORM
+
+temp1 = initial y position (is set but never used)
+
+=============================================================================
+*/
+
+statetype s_statplat    = {PLATFORMSPR, PLATFORMSPR, step, false, false, 32000, 0, 0, NULL, NULL, R_Draw, &s_statplat};
+
+/*
+===========================
+=
+= SpawnStaticPlat
+=
+===========================
+*/
+
+void SpawnStaticPlat(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = platformobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y=new->temp1 = CONVERT_TILE_TO_GLOBAL(tileY);
+	new->xdir = 0;
+	new->ydir = 1;
+	new->needtoclip = cl_noclip;
+	NewState(new, &s_statplat);
+}
+
+/*
+=============================================================================
+
+						  GO PLATFORMS
+
+temp1 = direction
+temp2 = countdown to next dir check
+
+=============================================================================
+*/
+
+statetype s_goplat        = {PLATFORMSPR,  PLATFORMSPR,  think,     false, false, 0, 0, 0, T_GoPlat, NULL, R_Draw, NULL};
+statetype s_slotgoplat1   = {SLOTPLAT1SPR, SLOTPLAT1SPR, stepthink, false, false, 0, 0, 0, T_GoSlotPlat, NULL, R_Draw, &s_slotgoplat2};
+statetype s_slotgoplat2   = {SLOTPLAT2SPR, SLOTPLAT2SPR, stepthink, false, false, 0, 0, 0, T_GoSlotPlat, NULL, R_Draw, &s_slotgoplat1};
+// BUG? the slotgoplat states have a tictime of 0, so they never transition to the next state
+
+/*
+===========================
+=
+= SpawnGoPlat
+=
+===========================
+*/
+
+void SpawnGoPlat(Uint16 tileX, Uint16 tileY, Sint16 dir, Sint16 type)
+{
+	GetNewObj(false);
+	new->obclass = platformobj;
+	new->active = ac_allways;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	new->xdir = 0;
+	new->ydir = 1;
+	new->needtoclip = cl_noclip;
+	if (type)
+	{
+		new->x += 4*PIXGLOBAL;
+		new->y += 4*PIXGLOBAL;
+		NewState(new, &s_slotgoplat1);
+	}
+	else
+	{
+		NewState(new, &s_goplat);
+	}
+	*(mapsegs[2]+mapbwidthtable[tileY]/2 + tileX) = DIRARROWSTART + dir;
+	new->temp1 = dir;
+	new->temp2 = TILEGLOBAL;
+}
+
+/*
+===========================
+=
+= T_GoPlat
+=
+===========================
+*/
+
+void T_GoPlat(objtype *ob)
+{
+	Uint16 move;
+	Uint16 tx, ty;
+	Sint16 dir;
+
+	//
+	// this code could be executed twice during the same frame because the
+	// object's animation/state changed during that frame, so don't update
+	// anything if we already have movement for the current frame i.e. the
+	// update code has already been executed this frame
+	//
+	if (!xtry && !ytry)
+	{
+		move = tics * 12;
+		if (ob->temp2 > move)
+		{
+			ob->temp2 = ob->temp2 - move;
+
+			dir = pdirx[ob->temp1];
+			if (dir == 1)
+			{
+				xtry = xtry + move;
+			}
+			else if (dir == -1)
+			{
+				xtry = xtry + -move;
+			}
+
+			dir = pdiry[ob->temp1];
+			if (dir == 1)
+			{
+				ytry = ytry + move;
+			}
+			else if (dir == -1)
+			{
+				ytry = ytry + -move;
+			}
+		}
+		else
+		{
+			dir = pdirx[ob->temp1];
+			if (dir == 1)
+			{
+				xtry += ob->temp2;
+			}
+			else if (dir == -1)
+			{
+				xtry += -ob->temp2;
+			}
+
+			dir = pdiry[ob->temp1];
+			if (dir == 1)
+			{
+				ytry += ob->temp2;
+			}
+			else if (dir == -1)
+			{
+				ytry += -ob->temp2;
+			}
+
+			tx = CONVERT_GLOBAL_TO_TILE(ob->x + xtry);
+			ty = CONVERT_GLOBAL_TO_TILE(ob->y + ytry);
+			ob->temp1 = *(mapsegs[2]+mapbwidthtable[ty]/2 + tx) - DIRARROWSTART;
+			if (ob->temp1 < arrow_North || ob->temp1 > arrow_None)
+			{
+				char error[60] = "Goplat moved to a bad spot: ";
+				char buf[5] = "";
+
+				strcat(error, itoa(ob->x, buf, 16));
+				strcat(error, ",");
+				strcat(error, itoa(ob->y, buf, 16));
+				Quit(error);
+			}
+
+			move -= ob->temp2;
+			ob->temp2 = TILEGLOBAL - move;
+
+			dir = pdirx[ob->temp1];
+			if (dir == 1)
+			{
+				xtry = xtry + move;
+			}
+			else if (dir == -1)
+			{
+				xtry = xtry - move;
+			}
+
+			dir = pdiry[ob->temp1];
+			if (dir == 1)
+			{
+				ytry = ytry + move;
+			}
+			else if (dir == -1)
+			{
+				ytry = ytry - move;
+			}
+		}
+	}
+}
+
+/*
+===========================
+=
+= T_GoSlotPlat
+=
+===========================
+*/
+
+void T_GoSlotPlat(objtype *ob)
+{
+	Uint16 move;
+	Uint16 tx, ty;
+	Sint16 dir;
+
+	//
+	// this code could be executed twice during the same frame because the
+	// object's animation/state changed during that frame, so don't update
+	// anything if we already have movement for the current frame i.e. the
+	// update code has already been executed this frame
+	//
+	if (!xtry && !ytry)
+	{
+		move = tics * 12;
+		if (ob->temp2 > move)
+		{
+			ob->temp2 = ob->temp2 - move;
+
+			dir = pdirx[ob->temp1];
+			if (dir == 1)
+			{
+				xtry = xtry + move;
+			}
+			else if (dir == -1)
+			{
+				xtry = xtry + -move;
+			}
+
+			dir = pdiry[ob->temp1];
+			if (dir == 1)
+			{
+				ytry = ytry + move;
+			}
+			else if (dir == -1)
+			{
+				ytry = ytry + -move;
+			}
+		}
+		else
+		{
+			dir = pdirx[ob->temp1];
+			if (dir == 1)
+			{
+				xtry += ob->temp2;
+			}
+			else if (dir == -1)
+			{
+				xtry += -ob->temp2;
+			}
+
+			dir = pdiry[ob->temp1];
+			if (dir == 1)
+			{
+				ytry += ob->temp2;
+			}
+			else if (dir == -1)
+			{
+				ytry += -ob->temp2;
+			}
+
+			tx = CONVERT_GLOBAL_TO_TILE(ob->x + xtry + 4*PIXGLOBAL);
+			ty = CONVERT_GLOBAL_TO_TILE(ob->y + ytry + 4*PIXGLOBAL);
+			ob->temp1 = *(mapsegs[2]+mapbwidthtable[ty]/2 + tx) - DIRARROWSTART;
+			if (ob->temp1 < arrow_North || ob->temp1 > arrow_None)
+			{
+				Quit("Goplat moved to a bad spot!");
+			}
+
+			move -= ob->temp2;
+			ob->temp2 = TILEGLOBAL - move;
+
+			dir = pdirx[ob->temp1];
+			if (dir == 1)
+			{
+				xtry = xtry + move;
+			}
+			else if (dir == -1)
+			{
+				xtry = xtry - move;
+			}
+
+			dir = pdiry[ob->temp1];
+			if (dir == 1)
+			{
+				ytry = ytry + move;
+			}
+			else if (dir == -1)
+			{
+				ytry = ytry - move;
+			}
+		}
+	}
+}
+
+/*
+=============================================================================
+
+						  VOLTEFACE
+
+temp1 = direction
+temp2 = countdown to next dir check
+
+=============================================================================
+*/
+
+statetype s_volte1     = {VOLTEFACE1SPR,    VOLTEFACE1SPR,    stepthink, false, false,   6, 0, 0, T_Volte, C_Volte, R_Draw, &s_volte2};
+statetype s_volte2     = {VOLTEFACE2SPR,    VOLTEFACE2SPR,    stepthink, false, false,   6, 0, 0, T_Volte, C_Volte, R_Draw, &s_volte3};
+statetype s_volte3     = {VOLTEFACE3SPR,    VOLTEFACE3SPR,    stepthink, false, false,   6, 0, 0, T_Volte, C_Volte, R_Draw, &s_volte4};
+statetype s_volte4     = {VOLTEFACE4SPR,    VOLTEFACE4SPR,    stepthink, false, false,   6, 0, 0, T_Volte, C_Volte, R_Draw, &s_volte1};
+statetype s_voltestun  = {VOLTEFACESTUNSPR, VOLTEFACESTUNSPR, step,      false, false, 300, 0, 0, NULL, NULL, R_Draw, &s_volte1};
+
+/*
+===========================
+=
+= SpawnVolte
+=
+===========================
+*/
+
+void SpawnVolte(Uint16 tileX, Uint16 tileY)
+{
+	Uint16 dir;
+	Uint16 far *map;
+
+	GetNewObj(false);
+	new->obclass = volteobj;
+	new->active = ac_allways;
+	new->priority = 2;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	new->needtoclip = cl_noclip;
+	NewState(new, &s_volte1);
+	map = mapsegs[2] + mapbwidthtable[tileY]/2 + tileX;
+	if (map[-1] == DIRARROWSTART + arrow_East)
+	{
+		dir = arrow_East;
+	}
+	else if (map[1] == DIRARROWSTART + arrow_West)
+	{
+		dir = arrow_West;
+	}
+	else if (*(map-mapwidth) == DIRARROWSTART + arrow_South)
+	{
+		dir = arrow_South;
+	}
+	else if (*(map+mapwidth) == DIRARROWSTART + arrow_North)
+	{
+		dir = arrow_North;
+	}
+	map[0] = dir + DIRARROWSTART;
+	new->temp1 = dir;
+	new->temp2 = TILEGLOBAL;
+}
+
+/*
+===========================
+=
+= T_Volte
+=
+===========================
+*/
+
+void T_Volte(objtype *ob)
+{
+	Uint16 move;
+	Uint16 tx, ty;
+	Sint16 dir;
+
+	//
+	// this code could be executed twice during the same frame because the
+	// object's animation/state changed during that frame, so don't update
+	// anything if we already have movement for the current frame i.e. the
+	// update code has already been executed this frame
+	//
+	if (!xtry && !ytry)
+	{
+		move = tics << 5;
+		if (ob->temp2 > move)
+		{
+			ob->temp2 = ob->temp2 - move;
+
+			dir = pdirx[ob->temp1];
+			if (dir == 1)
+			{
+				xtry = xtry + move;
+			}
+			else if (dir == -1)
+			{
+				xtry = xtry + -move;
+			}
+
+			dir = pdiry[ob->temp1];
+			if (dir == 1)
+			{
+				ytry = ytry + move;
+			}
+			else if (dir == -1)
+			{
+				ytry = ytry + -move;
+			}
+		}
+		else
+		{
+			dir = pdirx[ob->temp1];
+			if (dir == 1)
+			{
+				xtry += ob->temp2;
+			}
+			else if (dir == -1)
+			{
+				xtry += -ob->temp2;
+			}
+
+			dir = pdiry[ob->temp1];
+			if (dir == 1)
+			{
+				ytry += ob->temp2;
+			}
+			else if (dir == -1)
+			{
+				ytry += -ob->temp2;
+			}
+
+			tx = CONVERT_GLOBAL_TO_TILE(ob->x + xtry);
+			ty = CONVERT_GLOBAL_TO_TILE(ob->y + ytry);
+			ob->temp1 = *(mapsegs[2]+mapbwidthtable[ty]/2 + tx) - DIRARROWSTART;
+			if (ob->temp1 < arrow_North || ob->temp1 > arrow_None)
+			{
+				char error[60] = "Volte moved to a bad spot: ";
+				char buf[5] = "";
+
+				strcat(error, itoa(ob->x, buf, 16));
+				strcat(error, ",");
+				strcat(error, itoa(ob->y, buf, 16));
+				Quit(error);
+			}
+
+			move -= ob->temp2;
+			ob->temp2 = TILEGLOBAL - move;
+
+			dir = pdirx[ob->temp1];
+			if (dir == 1)
+			{
+				xtry = xtry + move;
+			}
+			else if (dir == -1)
+			{
+				xtry = xtry - move;
+			}
+
+			dir = pdiry[ob->temp1];
+			if (dir == 1)
+			{
+				ytry = ytry + move;
+			}
+			else if (dir == -1)
+			{
+				ytry = ytry - move;
+			}
+		}
+	}
+}
+
+/*
+===========================
+=
+= C_Volte
+=
+===========================
+*/
+
+void C_Volte(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+	else if (hit->obclass == stunshotobj)
+	{
+		ExplodeShot(hit);
+		ChangeState(ob, &s_voltestun);
+	}
+}
+
+/*
+=============================================================================
+
+						  SNEAKY PLATFORM
+
+temp1 = initial x position (is set but never used)
+
+=============================================================================
+*/
+
+statetype s_sneakplatsit    = {PLATFORMSPR, PLATFORMSPR, think, false, false,  0,   0, 0, T_SneakPlat, NULL, R_Draw, NULL};
+statetype s_sneakplatdodge  = {PLATFORMSPR, PLATFORMSPR, slide, false, false, 48,  32, 0, NULL, NULL, R_Draw, &s_sneakplatreturn};
+statetype s_sneakplatreturn = {PLATFORMSPR, PLATFORMSPR, slide, false, false, 96, -16, 0, NULL, NULL, R_Draw, &s_sneakplatsit};
+
+/*
+===========================
+=
+= SpawnSneakPlat
+=
+===========================
+*/
+
+void SpawnSneakPlat(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = platformobj;
+	new->active = ac_allways;
+	new->priority = 0;
+	new->x=new->temp1 = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	new->xdir = 0;
+	new->ydir = 1;
+	new->needtoclip = cl_noclip;
+	NewState(new, &s_sneakplatsit);
+}
+
+/*
+===========================
+=
+= T_SneakPlat
+=
+===========================
+*/
+
+void T_SneakPlat(objtype *ob)
+{
+	Sint16 dist;
+
+	if (player->state != &s_keenjump1)
+		return;
+
+	if (player->xdir == 1)
+	{
+		dist = ob->left-player->right;
+		if (dist > 4*TILEGLOBAL || dist < 0)
+			return;
+	}
+	else
+	{
+		dist = player->left-ob->right;
+		if (dist > 4*TILEGLOBAL || dist < 0)
+			return;
+	}
+	dist = player->y - ob->y;
+	if (dist < -6*TILEGLOBAL || dist > 6*TILEGLOBAL)
+		return;
+
+	ob->xdir = player->xdir;
+	ob->state = &s_sneakplatdodge;
+}
+
+/*
+=============================================================================
+
+						  CANNON
+
+temp1 = direction
+
+=============================================================================
+*/
+
+statetype s_cannon     = {0,            0,            step,      false, false, 120, 0, 0, NULL, NULL, R_Draw, &s_cannonfire};
+statetype s_cannonfire = {0,            0,            step,      true,  false,   1, 0, 0, T_Cannon, NULL, R_Draw, &s_cannon};
+statetype s_cshot1     = {LASER1SPR,    LASER1SPR,    stepthink, false, false,   8, 0, 0, T_Velocity, C_CShot, R_CShot, &s_cshot2};
+statetype s_cshot2     = {LASER2SPR,    LASER2SPR,    stepthink, false, false,   8, 0, 0, T_Velocity, C_CShot, R_CShot, &s_cshot3};
+statetype s_cshot3     = {LASER3SPR,    LASER3SPR,    stepthink, false, false,   8, 0, 0, T_Velocity, C_CShot, R_CShot, &s_cshot4};
+statetype s_cshot4     = {LASER4SPR,    LASER4SPR,    stepthink, false, false,   8, 0, 0, T_Velocity, C_CShot, R_CShot, &s_cshot1};
+statetype s_cshothit1  = {LASERHIT1SPR, LASERHIT1SPR, step,      false, false,  10, 0, 0, NULL, NULL, R_Draw, &s_cshothit2};
+statetype s_cshothit2  = {LASERHIT2SPR, LASERHIT2SPR, step,      false, false,  10, 0, 0, NULL, NULL, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnCannon
+=
+===========================
+*/
+
+void SpawnCannon(Uint16 tileX, Uint16 tileY, Sint16 dir)
+{
+	GetNewObj(false);
+	new->obclass = cannonobj;
+	new->active = ac_yes;
+	new->tileright = new->tileleft = tileX;
+	new->tiletop = new->tilebottom = tileY;
+	new->x = new->left = new->right = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = new->top = new->bottom = CONVERT_TILE_TO_GLOBAL(tileY);
+	new->temp1 = dir;
+	NewState(new, &s_cannon);
+}
+
+/*
+===========================
+=
+= T_Cannon
+=
+===========================
+*/
+
+void T_Cannon(objtype *ob)
+{
+	GetNewObj(true);
+	new->obclass = mshotobj;
+	new->active = ac_removable;
+	new->x = ob->x;
+	new->y = ob->y;
+	switch (ob->temp1)
+	{
+	case 0:
+		new->yspeed = -64;
+		break;
+	case 1:
+		new->xspeed = 64;
+		break;
+	case 2:
+		new->yspeed = 64;
+		break;
+	case 3:
+		new->xspeed = -64;
+	}
+	NewState(new, &s_cshot1);
+	SD_PlaySound(SND_ENEMYSHOT);
+}
+
+/*
+===========================
+=
+= C_CShot
+=
+===========================
+*/
+
+void C_CShot(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+		ChangeState(ob, &s_cshothit1);
+	}
+}
+
+/*
+===========================
+=
+= R_CShot
+=
+===========================
+*/
+
+void R_CShot(objtype *ob)
+{
+	if (ob->hitnorth || ob->hiteast || ob->hitsouth || ob->hitwest)
+	{
+		SD_PlaySound(SND_ENEMYSHOTEXPLODE);
+		ChangeState(ob, &s_cshothit1);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/KEEN5/K5_ACT2.C b/16/keen456/KEEN4-6/KEEN5/K5_ACT2.C
new file mode 100755
index 00000000..7148d462
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN5/K5_ACT2.C
@@ -0,0 +1,906 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+/*
+K5_ACT2.C
+=========
+
+Contains the following actor types (in this order):
+
+- Sparky
+- Little Ampton
+- Slicestar
+- Shelley
+
+*/
+
+#include "CK_DEF.H"
+
+/*
+=============================================================================
+
+						  SPARKY
+
+temp1 = charge countdown
+
+=============================================================================
+*/
+
+statetype s_sparkywalk1   = {SPARKYWALKL1SPR, SPARKYWALKR1SPR, step,  false, true,  8, 128, 0, T_Sparky, C_Sparky, R_Sparky, &s_sparkywalk2};
+statetype s_sparkywalk2   = {SPARKYWALKL2SPR, SPARKYWALKR2SPR, step,  false, true,  8, 128, 0, NULL, C_Sparky, R_Sparky, &s_sparkywalk3};
+statetype s_sparkywalk3   = {SPARKYWALKL3SPR, SPARKYWALKR3SPR, step,  false, true,  8, 128, 0, NULL, C_Sparky, R_Sparky, &s_sparkywalk4};
+statetype s_sparkywalk4   = {SPARKYWALKL4SPR, SPARKYWALKR4SPR, step,  false, true,  8, 128, 0, NULL, C_Sparky, R_Sparky, &s_sparkywalk1};
+statetype s_sparkylook1   = {SPARKYTURN1SPR,  SPARKYTURN1SPR,  step,  false, true,  6,   0, 0, NULL, C_Sparky, R_Draw, &s_sparkylook2};
+statetype s_sparkylook2   = {SPARKYTURN2SPR,  SPARKYTURN2SPR,  step,  false, true,  6,   0, 0, NULL, C_Sparky, R_Draw, &s_sparkylook3};
+statetype s_sparkylook3   = {SPARKYTURN3SPR,  SPARKYTURN3SPR,  step,  false, true,  6,   0, 0, NULL, C_Sparky, R_Draw, &s_sparkylook4};
+statetype s_sparkylook4   = {SPARKYWALKR1SPR, SPARKYWALKR1SPR, step,  false, true,  6,   0, 0, T_SparkyLookL, C_Sparky, R_Sparky, &s_sparkylook5};
+statetype s_sparkylook5   = {SPARKYTURN3SPR,  SPARKYTURN3SPR,  step,  false, true,  6,   0, 0, NULL, C_Sparky, R_Draw, &s_sparkylook6};
+statetype s_sparkylook6   = {SPARKYTURN2SPR,  SPARKYTURN3SPR,  step,  false, true,  6,   0, 0, NULL, C_Sparky, R_Draw, &s_sparkylook7};
+statetype s_sparkylook7   = {SPARKYTURN1SPR,  SPARKYTURN3SPR,  step,  false, true,  6,   0, 0, NULL, C_Sparky, R_Draw, &s_sparkylook8};
+statetype s_sparkylook8   = {SPARKYWALKL1SPR, SPARKYWALKR1SPR, step,  false, true,  6,   0, 0, T_SparkyLookR, C_Sparky, R_Sparky, &s_sparkywalk2};
+statetype s_sparkyspeed1  = {SPARKYWALKL1SPR, SPARKYWALKR1SPR, step,  true,  true,  4,   0, 0, NULL, C_Sparky, R_Sparky, &s_sparkyspeed2};
+statetype s_sparkyspeed2  = {SPARKYWALKL2SPR, SPARKYWALKR2SPR, step,  true,  true,  4,   0, 0, NULL, C_Sparky, R_Sparky, &s_sparkyspeed3};
+statetype s_sparkyspeed3  = {SPARKYWALKL3SPR, SPARKYWALKR3SPR, step,  true,  true,  4,   0, 0, NULL, C_Sparky, R_Sparky, &s_sparkyspeed4};
+statetype s_sparkyspeed4  = {SPARKYWALKL4SPR, SPARKYWALKR4SPR, step,  true,  true,  4,   0, 0, T_ChargeCount, C_Sparky, R_Sparky, &s_sparkyspeed1};
+statetype s_sparkycharge1 = {SPARKYWALKL1SPR, SPARKYWALKR1SPR, step,  true,  true,  4, 128, 0, NULL, C_Sparky, R_Sparky, &s_sparkycharge2};
+statetype s_sparkycharge2 = {SPARKYWALKL2SPR, SPARKYWALKR2SPR, step,  true,  true,  4, 128, 0, T_RunSnd1, C_Sparky, R_Sparky, &s_sparkycharge3};
+statetype s_sparkycharge3 = {SPARKYWALKL3SPR, SPARKYWALKR3SPR, step,  true,  true,  4, 128, 0, NULL, C_Sparky, R_Sparky, &s_sparkycharge4};
+statetype s_sparkycharge4 = {SPARKYWALKL4SPR, SPARKYWALKR4SPR, step,  true,  true,  4, 128, 0, T_RunSnd2, C_Sparky, R_Sparky, &s_sparkycharge1};
+statetype s_sparkyturn1   = {SPARKYTURN3SPR,  SPARKYTURN1SPR,  step,  false, true,  8,   0, 0, NULL, C_Sparky, R_Draw, &s_sparkyturn2};
+statetype s_sparkyturn2   = {SPARKYTURN2SPR,  SPARKYTURN2SPR,  step,  false, true,  8,   0, 0, NULL, C_Sparky, R_Draw, &s_sparkyturn3};
+statetype s_sparkyturn3   = {SPARKYTURN1SPR,  SPARKYTURN3SPR,  step,  false, true,  8,   0, 0, NULL, C_Sparky, R_Draw, &s_sparkywalk1};
+statetype s_sparkystun    = {SPARKYSTUNSPR,   SPARKYSTUNSPR,   think, false, false, 0,   0, 0, T_Projectile, NULL, R_Stunned, NULL};
+
+/*
+===========================
+=
+= SpawnSparky
+=
+===========================
+*/
+
+void SpawnSparky(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = sparkyobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -1*TILEGLOBAL;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	NewState(new, &s_sparkywalk1);
+}
+
+/*
+===========================
+=
+= T_Sparky
+=
+===========================
+*/
+
+void T_Sparky(objtype *ob)
+{
+	if (US_RndT() < 0x40)
+	{
+		ob->state = &s_sparkylook1;
+		xtry = 0;
+	}
+}
+
+/*
+===========================
+=
+= T_ChargeCount
+=
+===========================
+*/
+
+void T_ChargeCount(objtype *ob)
+{
+	if (--ob->temp1 == 0)
+		ob->state = &s_sparkycharge1;
+}
+
+/*
+===========================
+=
+= T_SparkyLookL
+=
+===========================
+*/
+
+void T_SparkyLookL(objtype *ob)
+{
+	Uint16 dist = player->bottom + TILEGLOBAL - ob->bottom;
+	if (dist > 2*TILEGLOBAL)
+		return;
+
+	if (player->x < ob->x)
+	{	
+		ob->xdir = -1;
+		SD_PlaySound(SND_SPARKYCHARGE);
+		ob->state = &s_sparkyspeed1;
+		ob->temp1 = 3;
+	}
+}
+
+/*
+===========================
+=
+= T_SparkyLookR
+=
+===========================
+*/
+
+void T_SparkyLookR(objtype *ob)
+{
+	Uint16 dist = player->bottom + TILEGLOBAL - ob->bottom;
+	if (dist > 2*TILEGLOBAL)
+		return;
+
+	if (player->x > ob->x)
+	{
+		ob->xdir = 1;
+		SD_PlaySound(SND_SPARKYCHARGE);
+		ob->state = &s_sparkyspeed1;
+		ob->temp1 = 3;
+	}
+}
+
+/*
+===========================
+=
+= T_RunSnd1
+=
+===========================
+*/
+
+#pragma argsused
+void T_RunSnd1(objtype *ob)
+{
+	SD_PlaySound(SND_WORLDWALK1);
+}
+
+/*
+===========================
+=
+= T_RunSnd2
+=
+===========================
+*/
+
+#pragma argsused
+void T_RunSnd2(objtype *ob)
+{
+	SD_PlaySound(SND_WORLDWALK1);
+}
+
+/*
+===========================
+=
+= C_Sparky
+=
+===========================
+*/
+
+void C_Sparky(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+	else if (hit->obclass == stunshotobj)
+	{
+		StunObj(ob, hit, &s_sparkystun);
+	}
+}
+
+/*
+===========================
+=
+= R_Sparky
+=
+===========================
+*/
+
+void R_Sparky(objtype *ob)
+{
+	if (ob->xdir == 1 && ob->hitwest)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = -1;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, &s_sparkyturn1);
+	}
+	else if (ob->xdir == -1 && ob->hiteast)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = 1;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, &s_sparkyturn1);
+	}
+	else if (!ob->hitnorth)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = -ob->xdir;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, &s_sparkyturn1);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+=============================================================================
+
+						  LITTLE AMPTON
+
+=============================================================================
+*/
+
+statetype s_amptonwalk1    = {AMTONWALKL1SPR, AMPTONWALKR1SPR, step,       false, true,  8, 128,  0, T_Ampton, C_Ampton, R_Ampton, &s_amptonwalk2};
+statetype s_amptonwalk2    = {AMTONWALKL2SPR, AMPTONWALKR2SPR, step,       false, true,  8, 128,  0, T_Ampton, C_Ampton, R_Ampton, &s_amptonwalk3};
+statetype s_amptonwalk3    = {AMTONWALKL3SPR, AMPTONWALKR3SPR, step,       false, true,  8, 128,  0, T_Ampton, C_Ampton, R_Ampton, &s_amptonwalk4};
+statetype s_amptonwalk4    = {AMTONWALKL4SPR, AMPTONWALKR4SPR, step,       false, true,  8, 128,  0, T_Ampton, C_Ampton, R_Ampton, &s_amptonwalk1};
+statetype s_amptonturn     = {AMPTONFACESPR,  AMPTONFACESPR,   step,       false, true,  8,   0,  0, NULL, C_Ampton, R_Draw, &s_amptonwalk1};
+statetype s_amptongrab1    = {AMPTONGRAB1SPR, AMPTONGRAB1SPR,  step,       false, true,  8,   0,  0, NULL, C_Ampton, R_Draw, &s_amptongrab2};
+statetype s_amptongrab2    = {AMPTONGRAB2SPR, AMPTONGRAB2SPR,  step,       false, true,  8,   0,  0, NULL, C_Ampton, R_Draw, &s_amptonclimb};
+statetype s_amptonclimb    = {AMPTONGRAB2SPR, AMPTONGRAB2SPR,  slidethink, false, false, 0,   0, 32, T_AmptonClimb, C_Ampton, R_Draw, NULL};
+statetype s_amptonrelease1 = {AMPTONGRAB2SPR, AMPTONGRAB2SPR,  step,       false, false, 8,   0,  0, NULL, C_Ampton, R_Draw, &s_amptonrelease2};
+statetype s_amptonrelease2 = {AMPTONGRAB1SPR, AMPTONGRAB1SPR,  step,       false, false, 8,   0,  0, T_SetNoThink, C_Ampton, R_Draw, &s_amptonwalk1};
+statetype s_amptonfiddle1  = {AMPTONGRAB1SPR, AMPTONGRAB1SPR,  step,       false, true, 12,   0,  0, NULL, C_Ampton, R_Draw, &s_amptonfiddle2};
+statetype s_amptonfiddle2  = {AMPTONGRAB2SPR, AMPTONGRAB2SPR,  step,       false, true, 12,   0,  0, NULL, C_Ampton, R_Draw, &s_amptonfiddle3};
+statetype s_amptonfiddle3  = {AMPTONGRAB1SPR, AMPTONGRAB1SPR,  step,       false, true, 12,   0,  0, NULL, C_Ampton, R_Draw, &s_amptonfiddle4};
+statetype s_amptonfiddle4  = {AMPTONGRAB2SPR, AMPTONGRAB2SPR,  step,       false, true, 12,   0,  0, NULL, C_Ampton, R_Draw, &s_amptonfiddle5};
+statetype s_amptonfiddle5  = {AMPTONGRAB1SPR, AMPTONGRAB1SPR,  step,       false, true, 12,   0,  0, T_SetNoThink, C_Ampton, R_Draw, &s_amptonwalk1};
+statetype s_amptonstun     = {AMPTONSTUNSPR,  AMPTONSTUNSPR,   think,      false, false, 0,   0,  0, T_Projectile, NULL, R_Stunned, NULL};
+
+/*
+===========================
+=
+= SpawnAmpton
+=
+===========================
+*/
+
+void SpawnAmpton(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = amptonobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -8*PIXGLOBAL;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	NewState(new, &s_amptonwalk1);
+}
+
+/*
+===========================
+=
+= T_Ampton
+=
+===========================
+*/
+
+void T_Ampton(objtype *ob)
+{
+	Uint16 far *map;
+	Uint16 intile, var8;
+	boolean poleup, poledown;
+
+	if (ob->state == &s_amptonwalk1)
+	{
+		SD_PlaySound(SND_AMPTONWALK1);
+	}
+	else if (ob->state == &s_amptonwalk3)
+	{
+		SD_PlaySound(SND_AMPTONWALK2);
+	}
+	if (ob->x & 0xFF)
+	{
+		map = mapsegs[1] + mapbwidthtable[ob->tiletop]/2 + ob->tileleft + 1;
+		intile = tinf[*map + INTILE] & INTILE_TYPEMASK;
+		if (intile == INTILE_AMPTONCOMPUTER)
+		{
+			ob->state = &s_amptonfiddle1;
+		}
+		else if (intile == INTILE_POLE && US_RndT() < 196)
+		{
+			if ((tinf[*(map + mapwidth*2) + INTILE] & INTILE_TYPEMASK) == INTILE_POLE)
+			{
+				poledown = true;
+			}
+			else
+			{
+				poledown = false;
+			}
+			if ((tinf[*(map - mapwidth*2) + INTILE] & INTILE_TYPEMASK) == INTILE_POLE)
+			{
+				poleup = true;
+			}
+			else
+			{
+				poleup = false;
+			}
+			if (poleup && poledown)
+			{
+				if (US_RndT() < 0x80)
+					poleup = false;
+				else
+					poledown = false;
+			}
+
+			if (poleup)
+			{
+				ob->ydir = -1;
+				ob->state = &s_amptongrab1;
+				ob->needtoclip = cl_noclip;
+				ob->nothink = 6;
+				xtry = 0;
+			}
+			else if (poledown)
+			{
+				ob->ydir = 1;
+				ob->state = &s_amptongrab1;
+				ob->needtoclip = cl_noclip;
+				ob->nothink = 6;
+				xtry = 0;
+			}
+		}
+	}
+}
+
+/*
+===========================
+=
+= T_AmptonClimb
+=
+===========================
+*/
+
+void T_AmptonClimb(objtype *ob)
+{
+	Uint16 newtile;
+	Uint16 far *map;
+	Uint16 move;
+
+	newtile = CONVERT_GLOBAL_TO_TILE(ob->bottom + ytry);
+	if (ob->tilebottom != newtile)
+	{
+		if (ob->ydir == -1)
+		{
+			map = mapsegs[1] + mapbwidthtable[newtile]/2 + ob->tileleft + 1;
+			if (!tinf[map[0] + NORTHWALL] && tinf[map[mapwidth]+NORTHWALL])
+			{
+				if ((tinf[*(map-4*mapwidth)+INTILE] & INTILE_TYPEMASK) == INTILE_POLE && US_RndT() < 0x80)
+					return;
+
+				move = (ob->bottom & 0xFF) + 1;
+				ob->y -= move;
+				ob->bottom -= move;
+				ob->needtoclip = cl_midclip;
+				ob->state = &s_amptonrelease1;
+				ytry = PIXGLOBAL;
+				ob->ydir = 1;
+				ClipToWalls(ob);
+				ob->nothink = 4;
+				return;
+			}
+			if ((tinf[*(map-mapwidth)+INTILE] & INTILE_TYPEMASK) != INTILE_POLE)
+			{
+				ytry = 0;
+				ob->ydir = 1;
+			}
+		}
+		else
+		{
+			map = mapsegs[1] + mapbwidthtable[newtile]/2 + ob->tileleft + 1;
+			if (tinf[map[0] + NORTHWALL] && !tinf[*(map-mapwidth)+NORTHWALL])
+			{
+				if ((tinf[map[2*mapwidth] + INTILE] & INTILE_TYPEMASK) == INTILE_POLE && US_RndT() < 0x80)
+					return;
+
+				move = 0xFF - (ob->bottom & 0xFF);
+				ob->y += move;
+				ob->bottom += move;
+				ob->needtoclip = cl_midclip;
+				ob->state = &s_amptonrelease1;
+				ytry = PIXGLOBAL;
+				ClipToWalls(ob);
+				ob->nothink = 4;
+				return;
+			}
+			if ((tinf[map[0] + INTILE] & INTILE_TYPEMASK) != INTILE_POLE)
+			{
+				ytry = 0;
+				ob->ydir = -1;
+			}
+		}
+	}
+}
+
+/*
+===========================
+=
+= T_SetNoThink
+=
+===========================
+*/
+
+void T_SetNoThink(objtype *ob)
+{
+	ob->nothink = 4;
+}
+
+/*
+===========================
+=
+= C_Ampton
+=
+===========================
+*/
+
+void C_Ampton(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		if (ob->state == &s_amptonclimb)
+		{
+			KillKeen();
+		}
+		else
+		{
+			ClipToSpriteSide(hit, ob);
+		}
+	}
+	else if (hit->obclass == stunshotobj)
+	{
+		ob->needtoclip = cl_midclip;
+		ob->ydir = 1;
+		ob->yspeed = 0;
+		SD_PlaySound(SND_AMPTONDIE);
+		StunObj(ob, hit, &s_amptonstun);
+	}
+}
+
+/*
+===========================
+=
+= R_Ampton
+=
+===========================
+*/
+
+void R_Ampton(objtype *ob)
+{
+	if (ob->xdir == 1 && ob->hitwest)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = -1;
+		ChangeState(ob, &s_amptonturn);
+	}
+	else if (ob->xdir == -1 && ob->hiteast)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = 1;
+		ChangeState(ob, &s_amptonturn);
+	}
+	else if (!ob->hitnorth)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = -ob->xdir;
+		ChangeState(ob, &s_amptonturn);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+=============================================================================
+
+						  SLICESTAR
+
+temp4 = health
+
+=============================================================================
+*/
+
+statetype s_slicestarslide  = {SLICESTARSPR,     SLICESTARSPR,     think, false, false,  0,  0,  0, T_Platform, C_Slicestar, R_Draw, NULL};
+statetype s_slicestarbounce = {SLICESTARSPR,     SLICESTARSPR,     slide, false, false,  0, 24, 24, NULL, C_Slicestar, R_Slicestar, &s_slicestarbounce};
+statetype s_slicestarboom   = {SLICESTARBOOMSPR, SLICESTARBOOMSPR, step,  false, false, 20,  0,  0, NULL, NULL, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnSlicestarSlide
+=
+===========================
+*/
+
+void SpawnSlicestarSlide(Uint16 tileX, Uint16 tileY, Sint16 dir)
+{
+	GetNewObj(false);
+	new->obclass = slicestarobj;
+	new->active = ac_yes;
+	new->priority = 2;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	new->temp4 = 20;	// health!
+	switch (dir)
+	{
+	case 0:
+		new->xdir = 0;
+		new->ydir = -1;
+		break;
+	case 1:
+		new->xdir = 1;
+		new->ydir = 0;
+		break;
+	case 2:
+		new->xdir = 0;
+		new->ydir = 1;
+		break;
+	case 3:
+		new->xdir = -1;
+		new->ydir = 0;
+	}
+	NewState(new, &s_slicestarslide);
+}
+
+/*
+===========================
+=
+= SpawnSlicestarBounce
+=
+===========================
+*/
+
+void SpawnSlicestarBounce(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = slicestarobj;
+	new->active = ac_yes;
+	new->priority = 2;
+	new->needtoclip = cl_fullclip;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	new->temp4 = 50;	// health!
+	switch (US_RndT() / 0x40)
+	{
+	case 0:
+		new->xdir = -1;
+		new->ydir = -1;
+		break;
+	case 1:
+		new->xdir = 1;
+		new->ydir = 1;
+		break;
+	case 2:
+		new->xdir = -1;
+		new->ydir = 1;
+		break;
+	case 3:
+		new->xdir = 1;
+		new->ydir = -1;
+	}
+	NewState(new, &s_slicestarbounce);
+}
+
+/*
+===========================
+=
+= C_Slicestar
+=
+===========================
+*/
+
+void C_Slicestar(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+	else if (hit->obclass == stunshotobj)
+	{
+		ExplodeShot(hit);
+		if (--ob->temp4 == 0)
+		{
+			ChangeState(ob, &s_slicestarboom);
+		}
+	}
+}
+
+/*
+===========================
+=
+= R_Slicestar
+=
+===========================
+*/
+
+void R_Slicestar(objtype *ob)
+{
+	if (ob->hitnorth)
+	{
+		ob->ydir = -1;
+		SD_PlaySound(SND_SLICESTARBOUNCE);
+	}
+	else if (ob->hitsouth)
+	{
+		ob->ydir = 1;
+		SD_PlaySound(SND_SLICESTARBOUNCE);
+	}
+	if (ob->hitwest)
+	{
+		ob->xdir = -1;
+		SD_PlaySound(SND_SLICESTARBOUNCE);
+	}
+	else if (ob->hiteast)
+	{
+		ob->xdir = 1;
+		SD_PlaySound(SND_SLICESTARBOUNCE);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+=============================================================================
+
+						  SHELLEY
+
+=============================================================================
+*/
+
+statetype s_shellywalk1  = {SHELLEYL1SPR,     SHELLEYR1SPR,     step,      false, true,    8, 128, 0, NULL, C_Shelly, R_Shelly, &s_shellywalk2};
+statetype s_shellywalk2  = {SHELLEYL2SPR,     SHELLEYR2SPR,     step,      false, true,    8, 128, 0, NULL, C_Shelly, R_Shelly, &s_shellywalk3};
+statetype s_shellywalk3  = {SHELLEYL3SPR,     SHELLEYR3SPR,     step,      false, true,    8, 128, 0, NULL, C_Shelly, R_Shelly, &s_shellywalk4};
+statetype s_shellywalk4  = {SHELLEYL4SPR,     SHELLEYR4SPR,     step,      false, true,    8, 128, 0, NULL, C_Shelly, R_Shelly, &s_shellywalk1};
+statetype s_shellylook   = {SHELLEYL2SPR,     SHELLEYR2SPR,     stepthink, false, true,  100,   0, 0, T_ShellyLook, C_Shelly, R_Draw, &s_shellylook2};
+statetype s_shellylook2  = {SHELLEYL2SPR,     SHELLEYR2SPR,     step,      true,  true,    1,   0, 0, T_Turn, C_Shelly, R_Draw, &s_shellywalk1};
+statetype s_shellyjump1  = {SHELLEYJUMPLSPR,  SHELLEYJUMPRSPR,  stepthink, false, false,   8,   0, 0, T_Projectile, C_Shelly, R_Shell, &s_shellyjump2};
+statetype s_shellyjump2  = {SHELLEYFALLLSPR,  SHELLEYFALLRSPR,  think,     false, false,   8,   0, 0, T_Projectile, C_Shelly, R_Shell, NULL};
+statetype s_shellydie    = {SHELLEYFALLLSPR,  SHELLEYFALLRSPR,  step,      false, false,   8,   0, 0, T_ShellyFrag, NULL, R_Shell, NULL};
+statetype s_shellydieup  = {SHELLEYL2SPR,     SHELLEYR2SPR,     step,      false, false,   8,   0, 0, T_ShellyFrag, NULL, R_Shell, NULL};
+statetype s_shellyboom1  = {SHELLEYBOOM1SPR,  SHELLEYBOOM1SPR,  step,      false, false,  20,   0, 0, NULL, C_Lethal, R_Draw, &s_shellyboom2};
+statetype s_shellyboom2  = {SHELLEYBOOM2SPR,  SHELLEYBOOM2SPR,  step,      false, false,  20,   0, 0, NULL, C_Lethal, R_Draw, &s_shellyboom3};
+statetype s_shellyboom3  = {SHELLEYBOOM3SPR,  SHELLEYBOOM3SPR,  step,      false, false,  20,   0, 0, NULL, C_Lethal, R_Draw, &s_shellyboom4};
+statetype s_shellyboom4  = {SHELLEYBOOM4SPR,  SHELLEYBOOM4SPR,  step,      false, false,  20,   0, 0, NULL, C_Lethal, R_Draw, NULL};
+statetype s_shellypiece1 = {SHELLEYPIECE1SPR, SHELLEYPIECE1SPR, think,     false, false,   8,   0, 0, T_Projectile, C_Lethal, R_Bounce, NULL};
+statetype s_shellypiece2 = {SHELLEYPIECE2SPR, SHELLEYPIECE2SPR, think,     false, false,   8,   0, 0, T_Projectile, C_Lethal, R_Bounce, NULL};
+
+/*
+===========================
+=
+= SpawnShelly
+=
+===========================
+*/
+
+void SpawnShelly(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = sparkyobj;	// BUG: should use shelleyobj
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	NewState(new, &s_shellywalk1);
+}
+
+/*
+===========================
+=
+= T_ShellyLook
+=
+===========================
+*/
+
+void T_ShellyLook(objtype *ob)
+{
+	Sint16 xdist;
+
+	if (player->top < ob->bottom)
+		return;
+
+	xdist = player->midx - ob->midx;
+	if (ob->xdir == 1)
+	{
+		if (xdist > 1*TILEGLOBAL && xdist < 3*TILEGLOBAL)
+		{
+			ob->xspeed = 16;
+			ob->yspeed = -24;
+			ob->state = &s_shellyjump1;
+			xtry = ytry = 0;
+		}
+	}
+	else
+	{
+		if (xdist < -1*TILEGLOBAL && xdist > -3*TILEGLOBAL)
+		{
+			ob->xspeed = -16;
+			ob->yspeed = -24;
+			ob->state = &s_shellyjump1;
+			xtry = ytry = 0;
+		}
+	}
+}
+
+/*
+===========================
+=
+= T_Turn
+=
+===========================
+*/
+
+void T_Turn(objtype *ob)
+{
+	ob->xdir = -ob->xdir;
+}
+
+/*
+===========================
+=
+= T_ShellyFrag
+=
+===========================
+*/
+
+void T_ShellyFrag(objtype *ob)
+{
+	GetNewObj(true);
+	new->x = ob->x;
+	new->y = ob->y;
+	new->xspeed = 32;
+	new->yspeed = -24;
+	NewState(new, &s_shellypiece1);
+
+	GetNewObj(true);
+	new->x = ob->x;
+	new->y = ob->y;
+	new->xspeed = -32;
+	new->yspeed = -24;
+	NewState(new, &s_shellypiece2);
+}
+
+/*
+===========================
+=
+= C_Shelly
+=
+===========================
+*/
+
+void C_Shelly(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		ClipToSpriteSide(hit, ob);
+		if (player->midx < ob->left || player->midx > ob->right)
+			return;
+	}
+	else if (hit->obclass == stunshotobj)
+	{
+		ExplodeShot(hit);
+	}
+	else if (hit->obclass == mshotobj)
+	{
+		RemoveObj(hit);
+	}
+	else
+		return;
+
+explode:
+	SD_PlaySound(SND_SHELLEYEXPLODE);
+	if (ob->hitnorth)
+	{
+		ChangeState(ob, &s_shellydieup);
+	}
+	else
+	{
+		ChangeState(ob, &s_shellydie);
+	}
+	GetNewObj(true);
+	new->x = ob->x;
+	new->y = ob->y;
+	NewState(new, &s_shellyboom1);
+}
+
+/*
+===========================
+=
+= R_Shelly
+=
+===========================
+*/
+
+void R_Shelly(objtype *ob)
+{
+	if (ob->xdir == 1 && ob->hitwest)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = -1;
+	}
+	else if (ob->xdir == -1 && ob->hiteast)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = 1;
+	}
+	else if (!ob->hitnorth)
+	{
+		ob->x -= ob->xmove;
+		ChangeState(ob, &s_shellylook);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+===========================
+=
+= R_Shell
+=
+===========================
+*/
+
+void R_Shell(objtype *ob)
+{
+	if (ob->hiteast || ob->hitwest)
+	{
+		ob->xspeed = 0;
+	}
+	if (ob->hitnorth)
+	{
+		SD_PlaySound(SND_SHELLEYEXPLODE);
+		ChangeState(ob, &s_shellydie);
+
+		GetNewObj(true);
+		new->x = ob->x;
+		new->y = ob->y;
+		NewState(new, &s_shellyboom1);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/KEEN5/K5_ACT3.C b/16/keen456/KEEN4-6/KEEN5/K5_ACT3.C
new file mode 100755
index 00000000..a0fa9c78
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN5/K5_ACT3.C
@@ -0,0 +1,2142 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+/*
+K5_ACT3.C
+=========
+
+Contains the following actor types (in this order):
+
+- Shikadi Mine
+- Robo Red
+- Spirogrip
+- Spindred
+- Shikadi Master
+- Shikadi
+- Shockshund
+- Sphereful
+- Scottie
+- QED
+
+*/
+
+#include "CK_DEF.H"
+
+/*
+=============================================================================
+
+						  SHIKADI MINE
+
+temp2 = x position of the "eye", in global units (relative to the mine sprite)
+temp3 = y position of the "eye", in global units (relative to the mine sprite)
+temp4 = sprite pointer for the "eye"
+
+=============================================================================
+*/
+
+static Uint16 dopposite[] = {2, 3, 0, 1, 6, 7, 4, 5, 8};
+
+statetype s_mine       = {SHIKADIMINESPR,       SHIKADIMINESPR,       think, false, false,  8, 0, 0, T_Mine, C_Solid, R_Mine, NULL};
+statetype s_minecenter = {SHIKADIMINESPR,       SHIKADIMINESPR,       think, false, false,  0, 0, 0, T_MineCenter, C_Solid, R_Mine, &s_mineshift};
+statetype s_mineshift  = {SHIKADIMINESPR,       SHIKADIMINESPR,       think, false, false,  0, 0, 0, T_MineShift, C_Solid, R_Mine, &s_mine};
+statetype s_mineboom1  = {SHIKADIMINEPULSE1SPR, SHIKADIMINEPULSE1SPR, step,  false, false, 10, 0, 0, NULL, C_Solid, R_Draw, &s_mineboom2};
+statetype s_mineboom2  = {SHIKADIMINEPULSE2SPR, SHIKADIMINEPULSE2SPR, step,  false, false, 10, 0, 0, NULL, C_Solid, R_Draw, &s_mineboom3};
+statetype s_mineboom3  = {SHIKADIMINEPULSE1SPR, SHIKADIMINEPULSE1SPR, step,  false, false, 10, 0, 0, NULL, C_Solid, R_Draw, &s_mineboom4};
+statetype s_mineboom4  = {SHIKADIMINEPULSE2SPR, SHIKADIMINEPULSE2SPR, step,  false, false, 10, 0, 0, T_MineFrag, C_Solid, R_Draw, &s_mineboom5};
+statetype s_mineboom5  = {SHIKADIMINEBOOM1SPR,  SHIKADIMINEBOOM1SPR,  step,  false, false, 20, 0, 0, NULL, C_Spindread, R_Draw, &s_mineboom6};
+statetype s_mineboom6  = {SHIKADIMINEBOOM2SPR,  SHIKADIMINEBOOM2SPR,  step,  false, false, 20, 0, 0, NULL, C_Spindread, R_Draw, NULL};
+statetype s_minepiece  = {SHIKADIMINEPIECESPR,  SHIKADIMINEPIECESPR,  think, false, false,  8, 0, 0, T_Projectile, C_MineFrag, R_Bounce, NULL};
+
+/*
+===========================
+=
+= SpawnMine
+=
+===========================
+*/
+
+void SpawnMine(Uint16 tileX, Uint16 tileY)
+{
+	Sint16 i;
+
+	GetNewObj(false);
+	new->obclass = mineobj;
+	new->active = ac_yes;
+	new->needtoclip = cl_noclip;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -(31*PIXGLOBAL + 1);
+	new->temp2 = 16*PIXGLOBAL;
+	new->temp3 = 13*PIXGLOBAL;
+	NewState(new, &s_mineshift);
+	new->xspeed = TILEGLOBAL;
+
+	for (i=0; i<=3; i++)
+	{
+		if (Walk(new, i))
+			break;
+	}
+}
+
+/*
+===========================
+=
+= MinePosCheck
+=
+===========================
+*/
+
+boolean MinePosCheck(Uint16 tileX, Uint16 tileY)
+{
+	Uint16 far *map;
+	Uint16 x, y, tile;
+
+	map = mapsegs[1] + mapbwidthtable[tileY]/2 + tileX;
+	for (y=0; y<2; y++)
+	{
+		for (x=0; x<3; x++)
+		{
+			tile = *(map + y*mapwidth + x);
+			if (tinf[tile+NORTHWALL] || tinf[tile+EASTWALL] || tinf[tile+SOUTHWALL] || tinf[tile+WESTWALL])
+				return false;
+		}
+	}
+	return true;
+}
+
+/*
+===========================
+=
+= Walk
+=
+===========================
+*/
+
+boolean Walk(objtype *ob, Sint16 dir)
+{
+	Uint16 tileX, tileY;
+
+	tileX = CONVERT_GLOBAL_TO_TILE(ob->x + xtry);
+	tileY = CONVERT_GLOBAL_TO_TILE(ob->y + ytry);
+
+	switch (dir)
+	{
+	case 0:
+		if (MinePosCheck(tileX, tileY-1))
+		{
+			ob->xdir = 0;
+			ob->ydir = -1;
+			return true;
+		}
+		return false;
+	case 1:
+		if (MinePosCheck(tileX+1, tileY))
+		{
+			ob->xdir = 1;
+			ob->ydir = 0;
+			return true;
+		}
+		return false;
+	case 2:
+		if (MinePosCheck(tileX, tileY+1))
+		{
+			ob->xdir = 0;
+			ob->ydir = 1;
+			return true;
+		}
+		return false;
+	case 3:
+		if (MinePosCheck(tileX-1, tileY))
+		{
+			ob->xdir = -1;
+			ob->ydir = 0;
+			return true;
+		}
+		return false;
+	default:
+		Quit("Walk: Bad dir");
+	}
+	return false;
+}
+
+/*
+===========================
+=
+= ChaseThink
+=
+===========================
+*/
+
+void ChaseThink(objtype *ob)
+{
+	Sint16 temp;
+	Sint16 xdist, ydist, ydir, xdir;
+	Sint16 olddir[2], oppdir;
+
+	if (ob->xdir == 1)
+	{
+		olddir[0] = 1;
+	}
+	else if (ob->xdir == -1)
+	{
+		olddir[0] = 3;
+	}
+	else if (ob->ydir == -1)
+	{
+		olddir[0] = 0;
+	}
+	else if (ob->ydir == 1)
+	{
+		olddir[0] = 2;
+	}
+	oppdir = dopposite[olddir[0]];
+	xdist = player->x - (ob->x + xtry);
+	ydist = player->y - (ob->y + ytry);
+	xdir = 8;
+	ydir = 8;
+	if (xdist > 0)
+	{
+		xdir = 1;
+	}
+	if (xdist < 0)
+	{
+		xdir = 3;
+	}
+	if (ydist > 0)
+	{
+		ydir = 2;
+	}
+	if (ydist < 0)
+	{
+		ydir = 0;
+	}
+	if (abs(ydist) > abs(xdist))
+	{
+		temp = xdir;
+		xdir = ydir;
+		ydir = temp;
+	}
+	if (xdir == oppdir)
+	{
+		xdir = 8;
+	}
+	if (ydir == oppdir)
+	{
+		ydir = 8;
+	}
+	if (ydir != 8 && Walk(ob, ydir))
+	{
+		return;
+	}
+	if (xdir != 8 && Walk(ob, xdir))
+	{
+		return;
+	}
+	if (Walk(ob, olddir[0]))
+	{
+		return;
+	}
+	if (US_RndT() > 0x80)
+	{
+		for (temp=0; temp<=3; temp++)
+		{
+			if (temp != oppdir && Walk(ob, temp))
+				return;
+		}
+	}
+	else
+	{
+		for (temp=3; temp>=0; temp--)
+		{
+			if (temp != oppdir && Walk(ob, temp))
+				return;
+		}
+	}
+	Walk(ob, oppdir);
+}
+
+/*
+===========================
+=
+= T_Mine
+=
+===========================
+*/
+
+void T_Mine(objtype *ob)
+{
+	Sint16 oldxdir, oldydir;
+	Sint16 xdist, ydist;
+	Sint16 speed;
+
+	xdist = ob->x - player->x;
+	ydist = ob->y - player->y;
+	if (xdist <= 2*TILEGLOBAL && xdist >= -5*TILEGLOBAL && ydist <= 3*TILEGLOBAL && ydist >= -5*PIXGLOBAL)
+	{
+		SD_PlaySound(SND_MINEEXPLODE);
+		ob->state = &s_mineboom1;
+		RF_RemoveSprite((void**)(&ob->temp4));
+	}
+	else
+	{
+		speed = tics * 10;
+		if (ob->xspeed <= speed)
+		{
+			xtry = ob->xdir * ob->xspeed;
+			ytry = ob->ydir * ob->xspeed;	// yes, this uses xspeed!
+			speed -= ob->xspeed;
+			oldxdir = ob->xdir;
+			oldydir = ob->ydir;
+			ChaseThink(ob);
+			ob->xspeed = TILEGLOBAL;
+			if (ob->xdir != oldxdir || ob->ydir != oldydir)
+			{
+				ob->state = &s_minecenter;
+				return;
+			}
+		}
+		ob->xspeed -= speed;
+		xtry += ob->xdir * speed;
+		ytry += ob->ydir * speed;
+	}
+}
+
+/*
+===========================
+=
+= C_Solid
+=
+===========================
+*/
+
+#pragma argsused
+void C_Solid(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == stunshotobj)
+	{
+		ExplodeShot(hit);
+	}
+}
+
+/*
+===========================
+=
+= C_MineFrag
+=
+===========================
+*/
+
+#pragma argsused
+void C_MineFrag(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == stunshotobj)
+	{
+		ExplodeShot(hit);
+	}
+	else if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+	else if (hit->obclass == qedobj)
+	{
+		SpawnFuseFlash(hit->tileleft, hit->tiletop);
+		SpawnFuseFlash(hit->tileright, hit->tiletop);
+		SpawnFuseFlash(hit->tileleft, hit->tilebottom);
+		SpawnFuseFlash(hit->tileright, hit->tilebottom);
+		RF_MapToMap(0, 0, 16, 11, 4, 2);
+		RF_MapToMap(4, 0, 16, 13, 4, 2);
+		SpawnDeadMachine();
+		RemoveObj(hit);
+	}
+}
+
+/*
+===========================
+=
+= T_MineCenter
+=
+===========================
+*/
+
+void T_MineCenter(objtype *ob)
+{
+	Sint16 px, py, xdist, ydist;
+
+	xdist = ob->x - player->x;
+	ydist = ob->y - player->y;
+
+	if (xdist <= 2*TILEGLOBAL && xdist >= -3*TILEGLOBAL && ydist <= 3*TILEGLOBAL && ydist >= -3*TILEGLOBAL)
+	{
+		//BUG? this doesn't play a sound
+		ob->state = &s_mineboom1;
+		RF_RemoveSprite((void**)&ob->temp4);
+	}
+	else
+	{
+		ob->needtoreact = true;
+
+		px = 16*PIXGLOBAL;
+		py = 13*PIXGLOBAL;
+
+		if (ob->temp2 < px)
+		{
+			ob->temp2 = ob->temp2 + tics*4;
+			if (ob->temp2 >= px)
+			{
+				ob->temp2 = px;
+				ob->state = ob->state->nextstate;
+			}
+		}
+		else if (ob->temp2 > px)
+		{
+			ob->temp2 = ob->temp2 - tics*4;
+			if (ob->temp2 <= px)
+			{
+				ob->temp2 = px;
+				ob->state = ob->state->nextstate;
+			}
+		}
+		if (ob->temp3 < py)
+		{
+			ob->temp3 = ob->temp3 + tics*4;
+			if (ob->temp3 >= py)
+			{
+				ob->temp3 = py;
+				ob->state = ob->state->nextstate;
+			}
+		}
+		else if (ob->temp3 > py)
+		{
+			ob->temp3 = ob->temp3 - tics*4;
+			if (ob->temp3 <= py)
+			{
+				ob->temp3 = py;
+				ob->state = ob->state->nextstate;
+			}
+		}
+	}
+}
+
+/*
+===========================
+=
+= T_MineShift
+=
+===========================
+*/
+
+void T_MineShift(objtype *ob)
+{
+	Sint16 px, py, xdist, ydist;
+
+	xdist = ob->x - player->x;
+	ydist = ob->y - player->y;
+
+	if (xdist <= 2*TILEGLOBAL && xdist >= -3*TILEGLOBAL && ydist <= 3*TILEGLOBAL && ydist >= -3*TILEGLOBAL)
+	{
+		//BUG? this doesn't play a sound
+		ob->state = &s_mineboom1;
+		RF_RemoveSprite((void**)&ob->temp4);
+	}
+	else
+	{
+		ob->needtoreact = true;
+
+		switch (ob->xdir)
+		{
+		case -1:
+			px = 8*PIXGLOBAL;
+			break;
+		case 0:
+			px = 16*PIXGLOBAL;
+			break;
+		case 1:
+			px = 24*PIXGLOBAL;
+		}
+		switch (ob->ydir)
+		{
+		case -1:
+			py = 5*PIXGLOBAL;
+			break;
+		case 0:
+			py = 13*PIXGLOBAL;
+			break;
+		case 1:
+			py = 21*PIXGLOBAL;
+		}
+
+		if (ob->temp2 < px)
+		{
+			ob->temp2 = ob->temp2 + tics*4;
+			if (ob->temp2 >= px)
+			{
+				ob->temp2 = px;
+				ob->state = ob->state->nextstate;
+			}
+		}
+		else if (ob->temp2 > px)
+		{
+			ob->temp2 = ob->temp2 - tics*4;
+			if (ob->temp2 <= px)
+			{
+				ob->temp2 = px;
+				ob->state = ob->state->nextstate;
+			}
+		}
+		if (ob->temp3 < py)
+		{
+			ob->temp3 = ob->temp3 + tics*4;
+			if (ob->temp3 >= py)
+			{
+				ob->temp3 = py;
+				ob->state = ob->state->nextstate;
+			}
+		}
+		else if (ob->temp3 > py)
+		{
+			ob->temp3 = ob->temp3 - tics*4;
+			if (ob->temp3 <= py)
+			{
+				ob->temp3 = py;
+				ob->state = ob->state->nextstate;
+			}
+		}
+	}
+}
+
+/*
+===========================
+=
+= T_MineFrag
+=
+===========================
+*/
+
+void T_MineFrag(objtype *ob)
+{
+	SD_PlaySound(SND_MINEEXPLODE);
+
+	GetNewObj(true);
+	new->x = ob->x;
+	new->y = ob->y;
+	new->xspeed = -(US_RndT()>>3);
+	new->yspeed = -48;
+	NewState(new, &s_minepiece);
+
+	GetNewObj(true);
+	new->x = ob->x + TILEGLOBAL;
+	new->y = ob->y;
+	new->xspeed = (US_RndT()>>3);
+	new->yspeed = -48;
+	NewState(new, &s_minepiece);
+
+	GetNewObj(true);
+	new->x = ob->x;
+	new->y = ob->y;
+	new->xspeed = (US_RndT()>>4) + 40;
+	new->yspeed = -24;
+	NewState(new, &s_minepiece);
+
+	GetNewObj(true);
+	new->x = ob->x + TILEGLOBAL;
+	new->y = ob->y;
+	new->xspeed = -40 - (US_RndT()>>4);
+	new->yspeed = -24;
+	NewState(new, &s_minepiece);
+
+	GetNewObj(true);
+	new->x = ob->x;
+	new->y = ob->y;
+	new->xspeed = 24;
+	new->yspeed = 16;
+	NewState(new, &s_minepiece);
+
+	GetNewObj(true);
+	new->x = ob->x + TILEGLOBAL;
+	new->y = ob->y;
+	new->xspeed = 24;
+	new->yspeed = 16;
+	NewState(new, &s_minepiece);
+}
+
+/*
+===========================
+=
+= R_Mine
+=
+===========================
+*/
+
+void R_Mine(objtype *ob)
+{
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+	RF_PlaceSprite((void**)&ob->temp4, ob->x+ob->temp2, ob->y+ob->temp3, SHIKADIMINEEYESPR, spritedraw, 2);
+}
+
+/*
+=============================================================================
+
+						  ROBO RED
+
+temp1 = number of shots to fire
+
+=============================================================================
+*/
+
+statetype s_robored      = {ROBOREDLSPR,     ROBOREDRSPR,     step,      false, true,  6, 64, 0, T_RoboRed, C_RoboRed, R_Walk, &s_robored};
+statetype s_roboredfire0 = {ROBOREDLSPR,     ROBOREDRSPR,     step,      true,  true, 40,  0, 0, NULL, C_Spindread, R_Draw, &s_roboredfire1};
+statetype s_roboredfire1 = {ROBOREDLSPR,     ROBOREDRSPR,     step,      true,  true,  4, 64, 0, NULL, C_Spindread, R_Draw, &s_roboredfire2};
+statetype s_roboredfire2 = {ROBOREDLSPR,     ROBOREDRSPR,     step,      false, true,  6,  0, 0, T_RoboShoot, C_Spindread, R_Draw, &s_roboredfire1};
+statetype s_rshot1       = {ROBOSHOT1SPR,    ROBOSHOT1SPR,    stepthink, false, false,  8,  0, 0, T_Velocity, C_RShot, R_RShot, &s_rshot2};
+statetype s_rshot2       = {ROBOSHOT2SPR,    ROBOSHOT2SPR,    stepthink, false, false,  8,  0, 0, T_Velocity, C_RShot, R_RShot, &s_rshot1};
+statetype s_rshothit1    = {ROBOSHOTHIT1SPR, ROBOSHOTHIT1SPR, step,      false, false, 10,  0, 0, NULL, NULL, R_Draw, &s_rshothit2};
+statetype s_rshothit2    = {ROBOSHOTHIT2SPR, ROBOSHOTHIT2SPR, step,      false, false, 10,  0, 0, NULL, NULL, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnRoboRed
+=
+===========================
+*/
+
+void SpawnRoboRed(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = roboredobj;
+	new->active = ac_yes;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -4*TILEGLOBAL;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	NewState(new, &s_robored);
+}
+
+/*
+===========================
+=
+= T_RoboRed
+=
+===========================
+*/
+
+void T_RoboRed(objtype *ob)
+{
+	if (!(ob->x & (4*PIXGLOBAL)) && player->bottom > ob->top && player->top < ob->bottom && US_RndT() < 16)
+	{
+		if (ob->x > player->x)
+		{
+			ob->xdir = -1;
+		}
+		else
+		{
+			ob->xdir = 1;
+		}
+		ob->temp1 = 10;	// shoot 10 times
+		ob->state = &s_roboredfire0;
+	}
+}
+
+/*
+===========================
+=
+= C_RoboRed
+=
+===========================
+*/
+
+void C_RoboRed(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == stunshotobj)
+	{
+		ExplodeShot(hit);
+		ob->xdir = (player->x > ob->x)? 1 : -1;
+		ob->temp1 = 10;	// shoot 10 times
+		ChangeState(ob, &s_roboredfire0);
+	}
+	else if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+}
+
+/*
+===========================
+=
+= T_RoboShoot
+=
+===========================
+*/
+
+void T_RoboShoot(objtype *ob)
+{
+	Uint16 x;
+
+	if (--ob->temp1 == 0)
+	{
+		ob->state = &s_robored;
+	}
+	if (ob->xdir == 1)
+	{
+		x = ob->x + 56*PIXGLOBAL;
+	}
+	else
+	{
+		x = ob->x;
+	}
+	if (CheckSpawnShot(x, ob->y + 32*PIXGLOBAL, &s_rshot1) != -1)
+	{
+		new->xspeed = ob->xdir * 60;
+		if (ob->temp1 & 1)
+		{
+			new->yspeed = 8;
+		}
+		else
+		{
+			new->yspeed = -8;
+		}
+		SD_PlaySound(SND_ENEMYSHOT);
+		xtry = (ob->xdir == 1)? -4*PIXGLOBAL : 4*PIXGLOBAL;
+	}
+}
+
+/*
+===========================
+=
+= C_RShot
+=
+===========================
+*/
+
+void C_RShot(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+		ChangeState(ob, &s_rshothit1);
+	}
+}
+
+/*
+===========================
+=
+= R_RShot
+=
+===========================
+*/
+
+void R_RShot(objtype *ob)
+{
+	if (ob->hitnorth || ob->hiteast || ob->hitsouth || ob->hitwest)
+	{
+		SD_PlaySound(SND_ENEMYSHOTEXPLODE);
+		ChangeState(ob, &s_rshothit1);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+=============================================================================
+
+						  SPIROGRIP
+
+=============================================================================
+*/
+
+statetype s_gripsitd  = {SPIROSITDSPR,   SPIROSITDSPR,   step,  false, false, 150,   0,   0, NULL, C_Spindread, R_Draw, &s_gripjumpd};
+statetype s_gripjumpd = {SPIROSITDSPR,   SPIROSITDSPR,   slide, false, false,  64,   0, -16, NULL, C_Spindread, R_Draw, &s_gripspin7};
+statetype s_gripsitl  = {SPIROSITLSPR,   SPIROSITLSPR,   step,  false, false, 150,   0,   0, NULL, C_Spindread, R_Draw, &s_gripjumpl};
+statetype s_gripjumpl = {SPIROSITLSPR,   SPIROSITLSPR,   slide, false, false,  64,  16,   0, NULL, C_Spindread, R_Draw, &s_gripspin1};
+statetype s_gripsitr  = {SPIROSITRSPR,   SPIROSITRSPR,   step,  false, false, 150,   0,   0, NULL, C_Spindread, R_Draw, &s_gripjumpr};
+statetype s_gripjumpr = {SPIROSITRSPR,   SPIROSITRSPR,   slide, false, false,  64, -16,   0, NULL, C_Spindread, R_Draw, &s_gripspin5};
+statetype s_gripsitu  = {SPIROSITUSPR,   SPIROSITUSPR,   step,  false, false, 150,   0,   0, NULL, C_Spindread, R_Draw, &s_gripjumpu};
+statetype s_gripjumpu = {SPIROSITUSPR,   SPIROSITUSPR,   slide, false, false,  64,   0,  16, NULL, C_Spindread, R_Draw, &s_gripspin3};
+statetype s_gripspin1 = {SPIROSPINULSPR, SPIROSPINULSPR, step,  false, false,   8,   0,   0, NULL, C_Spindread, R_Draw, &s_gripspin2};
+statetype s_gripspin2 = {SPIROSPINUSPR,  SPIROSPINUSPR,  step,  false, false,   8,   0,   0, T_SpiroLaunch, C_Spindread, R_Draw, &s_gripspin3};
+statetype s_gripspin3 = {SPIROSPINURSPR, SPIROSPINURSPR, step,  false, false,   8,   0,   0, NULL, C_Spindread, R_Draw, &s_gripspin4};
+statetype s_gripspin4 = {SPIROSPINRSPR,  SPIROSPINRSPR,  step,  false, false,   8,   0,   0, T_SpiroLaunch, C_Spindread, R_Draw, &s_gripspin5};
+statetype s_gripspin5 = {SPIROSPINDRSPR, SPIROSPINDRSPR, step,  false, false,   8,   0,   0, NULL, C_Spindread, R_Draw, &s_gripspin6};
+statetype s_gripspin6 = {SPIROSPINDSPR,  SPIROSPINDSPR,  step,  false, false,   8,   0,   0, T_SpiroLaunch, C_Spindread, R_Draw, &s_gripspin7};
+statetype s_gripspin7 = {SPIROSPINDLSPR, SPIROSPINDLSPR, step,  false, false,   8,   0,   0, NULL, C_Spindread, R_Draw, &s_gripspin8};
+statetype s_gripspin8 = {SPIROSPINLSPR,  SPIROSPINLSPR,  step,  false, false,   8,   0,   0, T_SpiroLaunch, C_Spindread, R_Draw, &s_gripspin1};
+statetype s_gripflyd  = {SPIROSITDSPR,   SPIROSITDSPR,   slide, false, false,   0,   0,  48, NULL, C_Spindread, R_SpiroFly, &s_gripsitd};
+statetype s_gripflyl  = {SPIROSITLSPR,   SPIROSITLSPR,   slide, false, false,   0, -48,   0, NULL, C_Spindread, R_SpiroFly, &s_gripsitl};
+statetype s_gripflyr  = {SPIROSITRSPR,   SPIROSITRSPR,   slide, false, false,   0,  48,   0, NULL, C_Spindread, R_SpiroFly, &s_gripsitr};
+statetype s_gripflyu  = {SPIROSITUSPR,   SPIROSITUSPR,   slide, false, false,   0,   0, -48, NULL, C_Spindread, R_SpiroFly, &s_gripsitu};
+
+/*
+===========================
+=
+= SpawnSpirogrip
+=
+===========================
+*/
+
+void SpawnSpirogrip(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = spirogripobj;
+	new->active = ac_yes;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -1*TILEGLOBAL;
+	new->xdir = 1;
+	new->ydir = 1;
+	NewState(new, &s_gripsitd);
+}
+
+/*
+===========================
+=
+= T_SpiroLaunch
+=
+===========================
+*/
+
+void T_SpiroLaunch(objtype *ob)
+{
+	if (US_RndT() <= 20)
+	{
+		SD_PlaySound(SND_SPIROFLY);
+		if (ob->state == &s_gripspin2)
+		{
+			ob->state = &s_gripflyu;
+		}
+		else if (ob->state == &s_gripspin4)
+		{
+			ob->state = &s_gripflyr;
+		}
+		else if (ob->state == &s_gripspin6)
+		{
+			ob->state = &s_gripflyd;
+		}
+		else if (ob->state == &s_gripspin8)
+		{
+			ob->state = &s_gripflyl;
+		}
+	}
+}
+
+/*
+===========================
+=
+= R_SpiroFly
+=
+===========================
+*/
+
+void R_SpiroFly(objtype *ob)
+{
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+	if (ob->hitnorth || ob->hiteast || ob->hitsouth || ob->hitwest)
+	{
+		ChangeState(ob, ob->state->nextstate);
+		SD_PlaySound(SND_SPIROGRAB);
+	}
+}
+
+/*
+=============================================================================
+
+						  SPINDRED
+
+temp1 = bounce counter
+
+=============================================================================
+*/
+
+statetype s_spindred1     = {SPINDRED1SPR, SPINDRED1SPR, stepthink, false, false, 8, 0, 0, T_Spindread, C_Spindread, R_Spindread, &s_spindred2};
+statetype s_spindred2     = {SPINDRED2SPR, SPINDRED2SPR, stepthink, false, false, 8, 0, 0, T_Spindread, C_Spindread, R_Spindread, &s_spindred3};
+statetype s_spindred3     = {SPINDRED3SPR, SPINDRED3SPR, stepthink, false, false, 8, 0, 0, T_Spindread, C_Spindread, R_Spindread, &s_spindred4};
+statetype s_spindred4     = {SPINDRED4SPR, SPINDRED4SPR, stepthink, false, false, 8, 0, 0, T_Spindread, C_Spindread, R_Spindread, &s_spindred1};
+
+/*
+===========================
+=
+= SpawnSpindread
+=
+===========================
+*/
+
+void SpawnSpindread(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = spindredobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -8*PIXGLOBAL;
+	new->ydir = 1;
+	NewState(new, &s_spindred1);
+}
+
+/*
+===========================
+=
+= T_Spindread
+=
+===========================
+*/
+
+void T_Spindread(objtype *ob)
+{
+	Sint32 i;
+
+	// BUG: this might be executed twice during the same frame if the
+	// object's animation/state changed during that frame, causing the
+	// object to move at twice the speed during that frame!
+	// To avoid that, return if ytry is not 0.
+
+	for (i=lasttimecount-tics; i<lasttimecount; i++)
+	{
+		if (i & 1)
+		{
+			if (ob->ydir == 1)
+			{
+				if (ob->yspeed < 0 && ob->yspeed >= -3)
+				{
+					ytry += ob->yspeed;
+					ob->yspeed = 0;
+					return;
+				}
+				else
+				{
+					ob->yspeed += 3;
+					if (ob->yspeed > 70)
+					{
+						ob->yspeed = 70;
+					}
+				}
+			}
+			else
+			{
+				if (ob->yspeed > 0 && ob->yspeed <= 3)
+				{
+					ytry += ob->yspeed;
+					ob->yspeed = 0;
+					return;
+				}
+				else
+				{
+					ob->yspeed -= 3;
+					if (ob->yspeed < -70)
+					{
+						ob->yspeed = -70;
+					}
+				}
+			}
+		}
+		ytry += ob->yspeed;
+	}
+}
+
+/*
+===========================
+=
+= C_Spindread
+=
+===========================
+*/
+
+#pragma argsused
+void C_Spindread(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == stunshotobj)
+	{
+		ExplodeShot(hit);
+	}
+	else if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+}
+
+/*
+===========================
+=
+= R_Spindread
+=
+===========================
+*/
+
+void R_Spindread(objtype *ob)
+{
+	if (ob->hitsouth)
+	{
+		ob->yspeed = 0;
+		if (ob->ydir == -1)
+		{
+			if (++ob->temp1 == 3)
+			{
+				ob->temp1 = 0;
+				ob->yspeed = 68;
+				ob->ydir = -ob->ydir;
+				SD_PlaySound(SND_SPINDREDFLIP);
+			}
+			else
+			{
+				SD_PlaySound(SND_SPINDREDBOUNCE);
+				ob->yspeed = 40;
+			}
+		}
+	}
+	if (ob->hitnorth)
+	{
+		ob->yspeed = 0;
+		if (ob->ydir == 1)
+		{
+			if (++ob->temp1 == 3)
+			{
+				ob->temp1 = 0;
+				ob->yspeed = -68;
+				ob->ydir = -ob->ydir;
+				SD_PlaySound(SND_BOUNCE);
+			}
+			else
+			{
+				SD_PlaySound(SND_SPINDREDBOUNCE);
+				ob->yspeed = -40;
+			}
+		}
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+=============================================================================
+
+						  SHIKADI MASTER
+
+temp1 = defines next action (0 = shoot, 1 = teleport)
+
+=============================================================================
+*/
+
+statetype s_master1      = {MASTER1SPR,           MASTER1SPR,           step,      false, false,  8, 0, 0, NULL, C_Master, R_Draw, &s_master2};
+statetype s_master2      = {MASTER2SPR,           MASTER2SPR,           step,      false, false,  8, 0, 0, NULL, C_Master, R_Draw, &s_master3};
+statetype s_master3      = {MASTER3SPR,           MASTER3SPR,           step,      false, false,  8, 0, 0, NULL, C_Master, R_Draw, &s_master4};
+statetype s_master4      = {MASTER4SPR,           MASTER4SPR,           step,      false, false,  8, 0, 0, T_Master, C_Master, R_Draw, &s_master1};
+statetype s_mastershoot1 = {SHIKMASTERCASTLSPR,   SHIKMASTERCASTRSPR,   step,      false, false, 30, 0, 0, T_MasterShoot, C_Spindread, R_Draw, &s_mastershoot2};
+statetype s_mastershoot2 = {SHIKMASTERCASTLSPR,   SHIKMASTERCASTRSPR,   step,      false, false,  8, 0, 0, NULL, C_Spindread, R_Draw, &s_master1};
+statetype s_mastertport1 = {MASTERTELEPORT1SPR,   MASTERTELEPORT1SPR,   step,      false, true,  20, 0, 0, NULL, C_Spindread, R_Draw, &s_mastertport2};
+statetype s_mastertport2 = {MASTERTELEPORT2SPR,   MASTERTELEPORT2SPR,   step,      false, true,  20, 0, 0, T_MasterTPort, C_Spindread, R_Draw, &s_mastertport3};
+statetype s_mastertport3 = {MASTERTELEPORT2SPR,   MASTERTELEPORT2SPR,   think,     false, false,  0, 0, 0, T_Projectile, NULL, R_Land, &s_mastertport4};
+statetype s_mastertport4 = {MASTERTELEPORT2SPR,   MASTERTELEPORT2SPR,   step,      false, false, 60, 0, 0, NULL, C_Spindread, R_Draw, &s_master1};
+statetype s_mshot1       = {MASTERSHOT4SPR,       MASTERSHOT1SPR,       stepthink, false, false,  8, 0, 0, T_WeakProjectile, C_MShot, R_MShot, &s_mshot2};
+statetype s_mshot2       = {MASTERSHOT3SPR,       MASTERSHOT2SPR,       stepthink, false, false,  8, 0, 0, T_WeakProjectile, C_MShot, R_MShot, &s_mshot3};
+statetype s_mshot3       = {MASTERSHOT2SPR,       MASTERSHOT3SPR,       stepthink, false, false,  8, 0, 0, T_WeakProjectile, C_MShot, R_MShot, &s_mshot4};
+statetype s_mshot4       = {MASTERSHOT1SPR,       MASTERSHOT4SPR,       stepthink, false, false,  8, 0, 0, T_WeakProjectile, C_MShot, R_MShot, &s_mshot1};
+statetype s_mspray1      = {MASTERFLOORSPARK1SPR, MASTERFLOORSPARK1SPR, stepthink, false, false,  6, 0, 0, T_Projectile, C_MShot, R_MSpray, &s_mspray2};
+statetype s_mspray2      = {MASTERFLOORSPARK2SPR, MASTERFLOORSPARK2SPR, stepthink, false, false,  6, 0, 0, T_Projectile, C_MShot, R_MSpray, &s_mspray3};
+statetype s_mspray3      = {MASTERFLOORSPARK3SPR, MASTERFLOORSPARK3SPR, stepthink, false, false,  6, 0, 0, T_Projectile, C_MShot, R_MSpray, &s_mspray4};
+statetype s_mspray4      = {MASTERFLOORSPARK4SPR, MASTERFLOORSPARK4SPR, stepthink, false, false,  6, 0, 0, T_Projectile, C_MShot, R_MSpray, &s_mspray1};
+
+/*
+===========================
+=
+= SpawnMaster
+=
+===========================
+*/
+
+void SpawnMaster(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = shikadimasterobj;
+	new->active = ac_yes;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -24*PIXGLOBAL;
+	NewState(new, &s_master1);
+}
+
+/*
+===========================
+=
+= T_Master
+=
+===========================
+*/
+
+void T_Master(objtype *ob)
+{
+	Sint16 randval;
+
+	randval = US_RndT();
+	if (randval < 0x40)
+	{
+		if (ob->temp1)
+		{
+			ob->state = &s_mastertport1;
+			ob->temp1 = 0;
+		}
+		else
+		{
+			ob->temp1 = 1;
+			if (player->x > ob->x)
+			{
+				ob->xdir = 1;
+			}
+			else
+			{
+				ob->xdir = -1;
+			}
+			ob->state = &s_mastershoot1;
+		}
+	}
+}
+
+/*
+===========================
+=
+= T_MasterShoot
+=
+===========================
+*/
+
+void T_MasterShoot(objtype *ob)
+{
+	Uint16 x;
+
+	if (ob->xdir == 1)
+	{
+		x = ob->x + 16*PIXGLOBAL;
+	}
+	else
+	{
+		x = ob->x;
+	}
+	if (CheckSpawnShot(x, ob->y+8*PIXGLOBAL, &s_mshot1) != -1)
+	{
+		new->xspeed = ob->xdir * 48;
+		new->yspeed = -16;
+		SD_PlaySound(SND_MASTERATTACK);
+	}
+}
+
+/*
+===========================
+=
+= C_Master
+=
+===========================
+*/
+
+void C_Master(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == stunshotobj)
+	{
+		ExplodeShot(hit);
+		ob->xdir = (player->x > ob->x)? 1 : -1;
+		ob->temp1 = 1;
+		ChangeState(ob, &s_mastershoot1);
+	}
+	else if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+}
+
+/*
+===========================
+=
+= T_MasterTPort
+=
+===========================
+*/
+
+void T_MasterTPort(objtype *ob)
+{
+	Uint16 tile;
+	Sint16 tx, ty, redos, oldx, oldy;
+
+	oldx = ob->x;
+	oldy = ob->y;
+
+	GetNewObj(true);
+	new->x = ob->x;
+	new->y = ob->y;
+	new->xspeed = 48;
+	NewState(new, &s_mspray1);	// BUG? new object is not made removable
+
+	GetNewObj(true);
+	new->x = ob->x;
+	new->y = ob->y;
+	new->xspeed = -48;
+	NewState(new, &s_mspray1);	// BUG? new object is not made removable
+
+	SD_PlaySound(SND_MASTERBLAST);
+
+	redos = 0;
+redo:
+	if (++redos == 10)
+	{
+		US_RndT();	// call it, but ignore the result
+		// probably to avoid repeatedly getting the same same "random" values
+		// due to having an even number of US_RndT() calls in this routine and
+		// an even number of elements in the random table.
+
+		ob->state = &s_master1;
+		ob->x = oldx - 1;
+		ob->y = oldy;
+		xtry = 1;
+		ytry = 0;
+	}
+	else
+	{
+		tx = player->tilemidx - 16 + (US_RndT()>>3);
+		ty = player->tilebottom - 16 + (US_RndT()>>3);
+		if (tx < 2 || ty < 2 || tx > mapwidth-5 || ty > mapheight-5)
+			goto redo;
+
+
+		ob->x = CONVERT_TILE_TO_GLOBAL(tx);
+		ob->y = CONVERT_TILE_TO_GLOBAL(ty);
+		ob->tileleft = tx-1;
+		ob->tileright = tx+4;
+		ob->tiletop = ty-1;
+		ob->tilebottom = ty+4;
+
+		{
+			Uint16 x, y;
+			Uint16 far *map;
+			Uint16 mapdelta;
+
+			map = (Uint16 far *)mapsegs[1] + mapbwidthtable[ob->tiletop]/2 + ob->tileleft;
+			mapdelta = mapwidth - (ob->tileright - ob->tileleft + 1);
+
+			for (y = ob->tiletop; ob->tilebottom >= y; y++, map+=mapdelta)
+			{
+				for (x = ob->tileleft; ob->tileright >= x; x++)
+				{
+					tile = *map++;
+					if ((tinf[tile+INTILE] & INTILE_FOREGROUND) || tinf[tile+NORTHWALL] || tinf[tile+EASTWALL]
+						|| tinf[tile+SOUTHWALL] || tinf[tile+WESTWALL])
+					{
+						goto redo;
+					}
+				}
+			}
+			xtry = ytry = 0;
+		}
+	}
+}
+
+/*
+===========================
+=
+= C_MShot
+=
+===========================
+*/
+
+void C_MShot(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+		RemoveObj(ob);
+	}
+	else if (hit->obclass == stunshotobj)
+	{
+		ExplodeShot(hit);
+		RemoveObj(ob);
+	}
+}
+
+/*
+===========================
+=
+= R_MShot
+=
+===========================
+*/
+
+void R_MShot(objtype *ob)
+{
+	if (ob->hiteast || ob->hitwest)
+	{
+		ob->xspeed = -ob->xspeed;
+	}
+	if (ob->hitsouth)
+	{
+		ob->yspeed = 0;
+	}
+	if (ob->hitnorth)
+	{
+		SD_PlaySound(SND_MASTERATTACK);
+		ob->xspeed = 48;
+		ChangeState(ob, &s_mspray1);
+
+		GetNewObj(true);
+		new->x = ob->x;
+		new->y = ob->y;
+		new->xspeed = -48;
+		NewState(new, &s_mspray1);	// BUG? new object is not made removable
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+===========================
+=
+= R_MSpray
+=
+===========================
+*/
+
+void R_MSpray(objtype *ob)
+{
+	if (ob->hiteast || ob->hitwest)
+	{
+		RemoveObj(ob);
+	}
+	else
+	{
+		RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+	}
+}
+
+/*
+=============================================================================
+
+						  SHIKADI
+
+temp1 = x tile position of the pole being grabbed (is set but never used)
+temp2 = health
+temp3 = flash countdown
+
+=============================================================================
+*/
+
+statetype s_shikadi1     = {SHIKADI1SPR,      SHIKADI1SPR,      step,  false, true,  8,   0, 0, NULL, C_Shikadi, R_Shikadi, &s_shikadi2};
+statetype s_shikadi2     = {SHIKADI2SPR,      SHIKADI2SPR,      step,  false, true,  8,   0, 0, NULL, C_Shikadi, R_Shikadi, &s_shikadi3};
+statetype s_shikadi3     = {SHIKADI3SPR,      SHIKADI3SPR,      step,  false, true,  8,   0, 0, NULL, C_Shikadi, R_Shikadi, &s_shikadi4};
+statetype s_shikadi4     = {SHIKADI4SPR,      SHIKADI4SPR,      step,  false, true,  8,   0, 0, NULL, C_Shikadi, R_Shikadi, &s_shikadiwalk1};
+statetype s_shikadiwalk1 = {SHIKADIWALKL1SPR, SHIKADIWALKR1SPR, step,  false, true,  8, 128, 0, T_Shikadi, C_Shikadi, R_Shikadi, &s_shikadiwalk2};
+statetype s_shikadiwalk2 = {SHIKADIWALKL2SPR, SHIKADIWALKR2SPR, step,  false, true,  8, 128, 0, T_Shikadi, C_Shikadi, R_Shikadi, &s_shikadiwalk3};
+statetype s_shikadiwalk3 = {SHIKADIWALKL3SPR, SHIKADIWALKR3SPR, step,  false, true,  8, 128, 0, T_Shikadi, C_Shikadi, R_Shikadi, &s_shikadiwalk4};
+statetype s_shikadiwalk4 = {SHIKADIWALKL4SPR, SHIKADIWALKR4SPR, step,  false, true,  8, 128, 0, T_Shikadi, C_Shikadi, R_Shikadi, &s_shikadiwalk1};
+statetype s_shikadigrab  = {SHIKADIGRABLSPR,  SHIKADIGRABRSPR,  step,  false, true, 20,   0, 0, T_PoleShock, C_Shikadi, R_Shikadi, &s_shikadigrab2};
+statetype s_shikadigrab2 = {SHIKADIGRABLSPR,  SHIKADIGRABRSPR,  step,  false, true, 20,   0, 0, NULL, C_Shikadi, R_Shikadi, &s_shikadiwalk1};
+statetype s_shikadistun  = {SHIKADISTUNSPR,   SHIKADISTUNSPR,   think, false, false, 0,   0, 0, T_Projectile, NULL, R_Stunned, NULL};
+
+statetype s_polespark1   = {SHIKADIPOLESPARK1SPR, SHIKADIPOLESPARK1SPR, stepthink, false, false,  0,   0, 0, T_PoleSpark, C_Lethal, R_Draw, &s_polespark2};
+statetype s_polespark2   = {SHIKADIPOLESPARK1SPR, SHIKADIPOLESPARK1SPR, stepthink, false, false,  0,   0, 0, T_PoleSpark, C_Lethal, R_Draw, &s_polespark1};
+
+/*
+===========================
+=
+= SpawnShikadi
+=
+===========================
+*/
+
+void SpawnShikadi(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = shikadiobj;
+	new->active = ac_yes;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -1*TILEGLOBAL;
+	new->temp2 = 4;	// health
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	NewState(new, &s_shikadi1);
+}
+
+/*
+===========================
+=
+= T_Shikadi
+=
+===========================
+*/
+
+void T_Shikadi(objtype *ob)
+{
+	Uint16 tx, tile;
+
+	if (player->state->contact == &KeenPosContact
+		|| ob->bottom - player->bottom + TILEGLOBAL <= 2*TILEGLOBAL)
+	{
+		if (ob->x > player->x + TILEGLOBAL)
+		{
+			ob->xdir = -1;
+		}
+		else if (ob->x < player->x - TILEGLOBAL)
+		{
+			ob->xdir = 1;
+		}
+		if (ob->xdir == 1)
+		{
+			tx = ob->tileright;
+		}
+		else
+		{
+			tx = ob->tileleft;
+		}
+
+		if (player->tilemidx != tx)
+			return;
+	}
+	else
+	{
+		if (US_RndT() < 0x10)
+		{
+			xtry = 0;
+			ob->state = &s_shikadi1;
+			return;
+		}
+		if ((ob->x & 0xFF) || !OnScreen(ob))
+			return;
+
+		if (ob->xdir == 1)
+		{
+			tx = ob->tileright;
+		}
+		else
+		{
+			tx = ob->tileleft;
+		}
+	}
+
+	tile = *(mapsegs[1]+mapbwidthtable[ob->tiletop]/2 + tx);
+	if (tinf[tile+INTILE] == INTILE_POLE)
+	{
+		ob->temp1 = tx;
+		ob->state = &s_shikadigrab;
+		xtry = 0;
+		SD_PlaySound(SND_SHIKADIATTACK);
+	}
+}
+
+/*
+===========================
+=
+= C_Shikadi
+=
+===========================
+*/
+
+void C_Shikadi(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+	if (hit->obclass == stunshotobj)
+	{
+		if (--ob->temp2 == 0)	// handle health
+		{
+			ob->xspeed = 0;
+			ob->yspeed = 0;
+			StunObj(ob, hit, &s_shikadistun);
+		}
+		else
+		{
+			ob->temp3 = 2;	// draw white two times
+			ob->needtoreact = true;
+			ExplodeShot(hit);
+		}
+	}
+}
+
+/*
+===========================
+=
+= T_PoleShock
+=
+===========================
+*/
+
+void T_PoleShock(objtype *ob)
+{
+	Uint16 x;
+
+	ob->nothink = 2;
+	if (ob->xdir == 1)
+	{
+		x = CONVERT_TILE_TO_GLOBAL(ob->tileright);
+	}
+	else
+	{
+		x = CONVERT_TILE_TO_GLOBAL(ob->tileleft);
+	}
+
+	GetNewObj(true);
+	new->x = x;
+	new->y = ob->y + 8*PIXGLOBAL;
+	new->obclass = mshotobj;
+	new->active = ac_removable;
+	new->needtoclip = cl_noclip;
+	NewState(new, &s_polespark1);
+	if (ob->y < player->y)
+	{
+		new->ydir = 1;
+	}
+	else
+	{
+		new->ydir = -1;
+	}
+	SD_PlaySound(SND_SHIKADIATTACK);
+}
+
+/*
+===========================
+=
+= T_PoleSpark
+=
+===========================
+*/
+
+void T_PoleSpark(objtype *ob)
+{
+	Uint16 tile;
+
+	if (ytry == 0)
+	{
+		ytry = ob->ydir * 48;
+		tile = *(mapsegs[1]+mapbwidthtable[ob->tiletop]/2 + ob->tilemidx);
+		if (tinf[tile+INTILE] != INTILE_POLE)
+		{
+			ob->state = NULL;
+		}
+	}
+}
+
+/*
+===========================
+=
+= R_Shikadi
+=
+===========================
+*/
+
+void R_Shikadi(objtype *ob)
+{
+	if (ob->xdir == 1 && ob->hitwest)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = -1;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	else if (ob->xdir == -1 && ob->hiteast)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = 1;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	else if (!ob->hitnorth)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = -ob->xdir;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	if (ob->temp3)
+	{
+		ob->temp3--;
+		RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, maskdraw, ob->priority);
+	}
+	else
+	{
+		RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+	}
+}
+
+/*
+=============================================================================
+
+						  PET (a.k.a. SHOCKSHUND)
+
+temp1 = countdown for sit animation
+temp2 = health
+temp3 = flash countdown
+
+=============================================================================
+*/
+
+statetype s_petsit1   = {PETSIT1SPR,      PETSIT1SPR,      step,      false, true,   8,   0, 0, NULL, C_Pet, R_Pet, &s_petsit2};
+statetype s_petsit2   = {PETSIT2SPR,      PETSIT2SPR,      step,      false, true,   8,   0, 0, T_PetSit, C_Pet, R_Pet, &s_petsit1};
+statetype s_petbark1  = {PETBARKL1SPR,    PETBARKR1SPR,    step,      false, true,   8,   0, 0, NULL, C_Pet, R_Pet, &s_petbark2};
+statetype s_petbark2  = {PETBARKL2SPR,    PETBARKR2SPR,    step,      false, true,   8,   0, 0, T_PetBark, C_Pet, R_Pet, &s_pet1};
+statetype s_pet1      = {PETRUNL1SPR,     PETRUNR1SPR,     step,      false, true,   8, 128, 0, NULL, C_Pet, R_Pet, &s_pet2};
+statetype s_pet2      = {PETRUNL2SPR,     PETRUNR2SPR,     step,      false, true,   8, 128, 0, NULL, C_Pet, R_Pet, &s_pet3};
+statetype s_pet3      = {PETRUNL3SPR,     PETRUNR3SPR,     step,      false, true,   8, 128, 0, NULL, C_Pet, R_Pet, &s_pet4};
+statetype s_pet4      = {PETRUNL4SPR,     PETRUNR4SPR,     step,      false, true,   8, 128, 0, T_Pet, C_Pet, R_Pet, &s_pet1};
+statetype s_petjump   = {PETJUMPLSPR,     PETJUMPRSPR,     think,     false, false,  8, 128, 0, T_Projectile, C_Pet, R_PetJump, &s_pet2};
+statetype s_pshot1    = {PETSPARK1SPR,    PETSPARK1SPR,    stepthink, false, false,  8,   0, 0, T_Velocity, C_PShot, R_PShot, &s_pshot2};
+statetype s_pshot2    = {PETSPARK2SPR,    PETSPARK2SPR,    stepthink, false, false,  8,   0, 0, T_Velocity, C_PShot, R_PShot, &s_pshot1};
+statetype s_pshothot1 = {PETSPARKHIT1SPR, PETSPARKHIT1SPR, step,      false, false, 10,   0, 0, NULL, NULL, R_Draw, &s_pshothot2};
+statetype s_pshothot2 = {PETSPARKHIT2SPR, PETSPARKHIT2SPR, step,      false, false, 10,   0, 0, NULL, NULL, R_Draw, NULL};
+statetype s_petstun   = {PETSTUNSPR,      PETSTUNSPR,      think,     false, false,  0,   0, 0, T_Projectile, NULL, R_Stunned, NULL};
+
+/*
+===========================
+=
+= SpawnPet
+=
+===========================
+*/
+
+void SpawnPet(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = petobj;
+	new->active = ac_yes;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -8*PIXGLOBAL;
+	new->temp2 = 2;	// health
+	new->xdir = new->ydir = 1;
+	NewState(new, &s_pet1);
+}
+
+/*
+===========================
+=
+= T_Pet
+=
+===========================
+*/
+
+void T_Pet(objtype *ob)
+{
+	if (ob->x > player->x)
+	{
+		ob->xdir = -1;
+	}
+	else
+	{
+		ob->xdir = 1;
+	}
+	if (US_RndT() < 0x10)
+	{
+		xtry = 0;
+		ob->state = &s_petsit1;
+		ob->temp1 = 10;	// repeat animation 10 times;
+	}
+	else
+	{
+		if (ob->bottom != player->bottom)
+		{
+			ob->state = &s_petjump;
+			if (ob->xdir == 1)
+			{
+				ob->xspeed = 40;
+			}
+			else
+			{
+				ob->xspeed = -40;
+			}
+			ob->yspeed = -40;
+		}
+		if (US_RndT() < 0x80)
+		{
+			xtry = 0;
+			ob->state = &s_petbark1;
+		}
+	}
+}
+
+/*
+===========================
+=
+= T_PetSit
+=
+===========================
+*/
+
+void T_PetSit(objtype *ob)
+{
+	if (--ob->temp1 == 0)
+	{
+		ob->state = &s_pet1;
+	}
+}
+
+/*
+===========================
+=
+= T_PetBark
+=
+===========================
+*/
+
+void T_PetBark(objtype *ob)
+{
+	Uint16 x;
+
+	if (ob->xdir == 1)
+	{
+		x = ob->x + 7*PIXGLOBAL;
+	}
+	else
+	{
+		x = ob->x;
+	}
+	if (CheckSpawnShot(x, ob->y+4*PIXGLOBAL, &s_pshot1) != -1)
+	{
+		new->xspeed = ob->xdir * 60;
+		new->xdir = ob->xdir;
+		SD_PlaySound(SND_SHOCKSHUNDBARK);
+	}
+}
+
+/*
+===========================
+=
+= C_Pet
+=
+===========================
+*/
+
+void C_Pet(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+	if (hit->obclass == stunshotobj)	// no 'else if' in the original code!
+	{
+		if (--ob->temp2 == 0)	// handle health
+		{
+			ob->xspeed = 0;
+			ob->yspeed = 0;
+			StunObj(ob, hit, &s_petstun);
+		}
+		else
+		{
+			ob->temp3 = 2;	// draw white two times
+			ob->needtoreact = true;
+			ExplodeShot(hit);
+		}
+	}
+}
+
+/*
+===========================
+=
+= R_Pet
+=
+===========================
+*/
+
+void R_Pet(objtype *ob)
+{
+	if (ob->xdir == 1 && ob->hitwest)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = -1;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	else if (ob->xdir == -1 && ob->hiteast)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = 1;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	else if (!ob->hitnorth)
+	{
+		if ((ob->xdir == 1 && player->x > ob->x) || (ob->xdir == -1 && player->x < ob->x))
+		{
+			ChangeState(ob, &s_petjump);
+			if (ob->xdir == 1)
+			{
+				ob->xspeed = 40;
+			}
+			else
+			{
+				ob->xspeed = -40;
+			}
+			ob->yspeed = -40;
+		}
+		else
+		{
+			ob->x -= ob->xmove*2;
+			ob->xdir = -ob->xdir;
+			ob->nothink = US_RndT() >> 5;
+			ChangeState(ob, ob->state);
+		}
+	}
+	if (ob->temp3)
+	{
+		ob->temp3--;
+		RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, maskdraw, ob->priority);
+	}
+	else
+	{
+		RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+	}
+}
+
+/*
+===========================
+=
+= R_PetJump
+=
+===========================
+*/
+
+void R_PetJump(objtype *ob)
+{
+	if (ob->hitnorth)
+	{
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, &s_pet1);
+	}
+	if (ob->temp3)
+	{
+		ob->temp3--;
+		RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, maskdraw, ob->priority);
+	}
+	else
+	{
+		RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+	}
+}
+
+/*
+===========================
+=
+= C_PShot
+=
+===========================
+*/
+
+void C_PShot(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+		ChangeState(ob, &s_pshothot1);
+	}
+	else if (hit->obclass == stunshotobj)
+	{
+		ExplodeShot(hit);
+		ChangeState(ob, &s_pshothot1);
+	}
+}
+
+/*
+===========================
+=
+= R_PShot
+=
+===========================
+*/
+
+void R_PShot(objtype *ob)
+{
+	if (ob->hitnorth || ob->hiteast || ob->hitsouth || ob->hitwest)
+	{
+		SD_PlaySound(SND_SHOCKBALLEXPLODE);
+		ChangeState(ob, &s_pshothot1);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+=============================================================================
+
+						  SPHEREFUL
+
+temp1 ... temp4 = sprite pointers for the guards circling around the sphere
+
+=============================================================================
+*/
+
+statetype s_sphereful1    = {SPHEREFUL1SPR, SPHEREFUL1SPR, stepthink, false, false, 6, 0, 0, T_Sphereful, C_Spindread, R_Sphereful, &s_sphereful2};
+statetype s_sphereful2    = {SPHEREFUL2SPR, SPHEREFUL2SPR, stepthink, false, false, 6, 0, 0, T_Sphereful, C_Spindread, R_Sphereful, &s_sphereful3};
+statetype s_sphereful3    = {SPHEREFUL3SPR, SPHEREFUL3SPR, stepthink, false, false, 6, 0, 0, T_Sphereful, C_Spindread, R_Sphereful, &s_sphereful4};
+statetype s_sphereful4    = {SPHEREFUL4SPR, SPHEREFUL4SPR, stepthink, false, false, 6, 0, 0, T_Sphereful, C_Spindread, R_Sphereful, &s_sphereful1};
+
+/*
+===========================
+=
+= SpawnSphereful
+=
+===========================
+*/
+
+void SpawnSphereful(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = spherefulobj;
+	new->needtoclip = cl_fullclip;
+	new->active = ac_yes;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -1*TILEGLOBAL;
+	new->priority = 1;
+	NewState(new, &s_sphereful1);
+}
+
+/*
+===========================
+=
+= T_Sphereful
+=
+===========================
+*/
+
+void T_Sphereful(objtype *ob)
+{
+	Sint32 i;
+	ob->needtoreact = true;
+
+	//
+	// this code could be executed twice during the same frame because the
+	// object's animation/state changed during that frame, so don't update
+	// anything if we already have movement for the current frame i.e. the
+	// update code has already been executed this frame
+	//
+	if (xtry == 0 && ytry == 0)
+	{
+		for (i=lasttimecount-tics; i<lasttimecount; i++)
+		{
+			if (!(i & 0xF))
+			{
+				if (ob->yspeed < 8)
+					ob->yspeed++;
+
+				if (ob->x < player->x && ob->xspeed < 8)
+					ob->xspeed++;
+
+				if (ob->x > player->x && ob->xspeed > -8)
+					ob->xspeed--;
+			}
+			ytry += ob->yspeed;
+			xtry += ob->xspeed;
+		}
+	}
+}
+
+/*
+===========================
+=
+= R_Sphereful
+=
+===========================
+*/
+
+void R_Sphereful(objtype *ob)
+{
+	static Uint16 circle[16] = {
+		384, 369, 328, 265, 192, 119,  58,  15,
+		  0,  15,  58, 119, 192, 265, 328, 369
+	};
+
+	Uint16 index, shapenum, priority;
+
+	if (ob->hitwest || ob->hiteast)
+	{
+		ob->xspeed = -ob->xspeed;
+		SD_PlaySound(SND_SPHEREFULBOUNCE);
+	}
+	if (ob->hitsouth)
+	{
+		ob->yspeed = -ob->yspeed;
+		SD_PlaySound(SND_SPHEREFULBOUNCE);
+	}
+
+	if (ob->hitnorth)
+	{
+		ob->yspeed = -ob->yspeed;
+		if (player->y < ob->y)
+		{
+			ob->yspeed--;
+		}
+		else
+		{
+			ob->yspeed++;
+		}
+		if (ob->yspeed > -4)
+		{
+			ob->yspeed = -4;
+		}
+		else if (ob->yspeed < -12)
+		{
+			ob->yspeed = -12;
+		}
+		SD_PlaySound(SND_BOUNCE);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+
+	index = ((Uint16)lasttimecount / 8) & 0xF;
+	shapenum = index / 4 + SPHEREGUARD1SPR;
+	if (index >= 8)
+	{
+		priority = 2;
+	}
+	else
+	{
+		priority = 0;
+	}
+	RF_PlaceSprite((void**)&ob->temp1, ob->x+circle[index], ob->y+circle[index], shapenum, spritedraw, priority);
+	RF_PlaceSprite((void**)&ob->temp2, ob->x+24*PIXGLOBAL-circle[index], ob->y+circle[index], shapenum, spritedraw, priority);
+
+	index += 8;
+	index &= 0xF;
+	if (index >= 8)
+	{
+		priority = 2;
+	}
+	else
+	{
+		priority = 0;
+	}
+	RF_PlaceSprite((void**)&ob->temp3, ob->x+circle[index], ob->y+circle[index], shapenum, spritedraw, priority);
+	RF_PlaceSprite((void**)&ob->temp4, ob->x+24*PIXGLOBAL-circle[index], ob->y+circle[index], shapenum, spritedraw, priority);
+}
+
+/*
+=============================================================================
+
+						  SCOTTIE
+
+=============================================================================
+*/
+
+statetype s_scottie1    = {SCOTTIEWALKL1SPR, SCOTTIEWALKR1SPR, step,  false, true,  8, 128, 0, T_Scottie, C_Scottie, R_Walk, &s_scottie2};
+statetype s_scottie2    = {SCOTTIEWALKL2SPR, SCOTTIEWALKR2SPR, step,  false, true,  8, 128, 0, T_Scottie, C_Scottie, R_Walk, &s_scottie3};
+statetype s_scottie3    = {SCOTTIEWALKL3SPR, SCOTTIEWALKR3SPR, step,  false, true,  8, 128, 0, T_Scottie, C_Scottie, R_Walk, &s_scottie4};
+statetype s_scottie4    = {SCOTTIEWALKL4SPR, SCOTTIEWALKR4SPR, step,  false, true,  8, 128, 0, T_Scottie, C_Scottie, R_Walk, &s_scottie1};
+statetype s_scottieface = {SCOTTIEFACESPR,   SCOTTIEFACESPR,   step,  false, true, 30,   0, 0, NULL, C_Scottie, R_Walk, &s_scottie1};
+statetype s_scottiestun = {SCOTTIESTUNSPR,   SCOTTIESTUNSPR,   think, false, false, 0,   0, 0, T_Projectile, NULL, R_Stunned, NULL};
+
+/*
+===========================
+=
+= SpawnScottie
+=
+===========================
+*/
+
+void SpawnScottie(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = scottieobj;
+	new->active = ac_yes;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -8*PIXGLOBAL;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	NewState(new, &s_scottie1);
+}
+
+/*
+===========================
+=
+= T_Scottie
+=
+===========================
+*/
+
+void T_Scottie(objtype *ob)
+{
+	if (US_RndT() < 0x10)
+	{
+		xtry = 0;
+		if (US_RndT() < 0x80)
+		{
+			ob->xdir = 1;
+		}
+		else
+		{
+			ob->xdir = -1;
+		}
+		ob->state = &s_scottieface;
+	}
+}
+
+/*
+===========================
+=
+= C_Scottie
+=
+===========================
+*/
+
+void C_Scottie(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj && hit->state->contact)
+	{
+		ClipToSpriteSide(hit, ob);
+	}
+	else if (hit->obclass == stunshotobj)
+	{
+		StunObj(ob, hit, &s_scottiestun);
+	}
+}
+
+/*
+=============================================================================
+
+						  QED
+
+=============================================================================
+*/
+
+statetype s_qed = {-1, -1, step, false, true, 8, 128, 0, NULL, NULL, NULL, &s_qed};
+
+/*
+===========================
+=
+= SpawnQed
+=
+===========================
+*/
+
+void SpawnQed(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = qedobj;
+	new->active = ac_yes;
+	new->tileleft = tileX;
+	new->tiletop = tileY;
+	new->tileright = new->tileleft + 1;
+	new->tilebottom = new->tiletop + 1;
+	new->x = new->left = CONVERT_TILE_TO_GLOBAL(tileX) + -1*PIXGLOBAL;
+	new->y = new->top = CONVERT_TILE_TO_GLOBAL(tileY) + -1*PIXGLOBAL;
+	new->right = new->left + 34*PIXGLOBAL;
+	new->bottom = new->top + 34*PIXGLOBAL;
+	NewState(new, &s_qed);
+}
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/KEEN5/K5_DEF.H b/16/keen456/KEEN4-6/KEEN5/K5_DEF.H
new file mode 100755
index 00000000..b6fc078e
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN5/K5_DEF.H
@@ -0,0 +1,485 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+#ifndef __K5_DEF__
+#define __K5_DEF__
+
+/*
+=============================================================================
+
+						GLOBAL CONSTANTS
+
+=============================================================================
+*/
+
+#if GRMODE == CGAGR
+#define MINMEMORY 255000l
+#else
+#define MINMEMORY 310000l
+#endif
+
+#define STARPALETTE   {0, 1, 24, 30, 31, 28, 6, 7, 19, 19, 19, 19, 19, 19, 19, 19, 0}
+#define INTROPALETTE  {0, 4, 4, 28, 1, 1, 1, 1, 17, 17, 17, 17, 19, 19, 19, 19, 0}
+#define SHRINKPALETTE {0, 4, 4, 28, 1, 1, 1, 1, 17, 17, 17, 17, 19, 19, 19,  4, 0}
+
+#define HIGHSCORE_LEFT	40
+#define HIGHSCORE_TOP	35
+#define HIGHSCORE_RIGHT	280
+#define HIGHSCORE_MAP	15
+
+#define STATUS_PRESSKEY_X 120
+
+#define WORLDMAPNAME	"Armageddon"
+#define DROPSNAME	"VITALIN"
+
+#define STARWARSMUSIC	17
+#define ENDINGMUSIC	14
+
+// levels in this range can NOT be re-entered (BWB level should be > MAXDONELEVEL)
+#define MINDONELEVEL 1
+#define MAXDONELEVEL 17
+
+#define INACTIVATEDIST 6
+
+//
+// tiles for worldmap teleporters
+//
+#define TELEPORTERTILE1 2687	// tile animation for teleporting out
+#define TELEPORTERTILE2 1063	// tile after teleporting out
+#define TELEPORTERTILE3 TELEPORTERTILE1	// tile animation for teleporting in
+#define TELEPORTERTILE4 0	// tile after teleporting in
+
+#define TELEPORERTILEMASK 1	// animation has 2 frames
+
+/*
+=============================================================================
+
+						K5_SPEC DEFINITIONS
+
+=============================================================================
+*/
+
+extern char far swtext[];
+extern char far *levelnames[GAMELEVELS];
+extern char far *levelenter[GAMELEVELS];
+
+void OpenMapDoor(Sint16 tileX, Sint16 tileY);
+void CloseMapDoor(Sint16 tileX, Sint16 tileY);
+void ScanInfoPlane(void);
+void GameOver(void);
+
+void FinishedFuse(void);
+
+/*
+=============================================================================
+
+						K5_ACT1 DEFINITIONS
+
+=============================================================================
+*/
+
+extern Sint16 pdirx[];
+extern Sint16 pdiry[];
+
+Sint16 CheckSpawnShot(Uint16 x, Uint16 y, statetype *state);
+void C_ClipSide(objtype *ob, objtype *hit);
+void C_ClipTop(objtype *ob, objtype *hit);
+void R_Land(objtype *ob);
+void R_Bounce(objtype *ob);
+
+extern statetype s_bonus1;
+extern statetype s_bonus2;
+extern statetype s_bonusfly1;
+extern statetype s_bonusfly2;
+extern statetype s_bonusrise;
+extern statetype s_splash1;
+extern statetype s_splash2;
+extern statetype s_splash3;
+extern statetype s_splash4;
+
+extern Uint16 bonusshape[];
+
+void SpawnBonus(Uint16 tileX, Uint16 tileY, Uint16 type);
+void SpawnSplash(Uint16 tileX, Uint16 tileY);
+void T_Bonus(objtype *ob);
+void T_FlyBonus(objtype *ob);
+
+extern statetype s_teleport1;
+extern statetype s_teleport2;
+extern statetype s_teleportzap1;
+extern statetype s_teleportzap2;
+
+void SpawnTeleport(void);
+
+extern statetype s_fuseflash1;
+extern statetype s_fuseflash2;
+extern statetype s_fuseflash3;
+
+void SpawnFuseFlash(Uint16 tileX, Uint16 tileY);
+
+extern statetype s_deadmachine;
+
+void SpawnDeadMachine(void);
+void T_DeadMachine(objtype *ob);
+
+extern statetype s_platform;
+extern statetype s_slotplat1;
+extern statetype s_slotplat2;
+
+void SpawnPlatform(Uint16 tileX, Uint16 tileY, Sint16 dir, Sint16 type);
+void T_Platform(objtype *ob);
+void T_Slotplat(objtype *ob);
+
+extern statetype s_dropplatsit;
+extern statetype s_dropplatfall;
+extern statetype s_dropplatrise;
+
+void SpawnDropPlat(Uint16 tileX, Uint16 tileY);
+void T_DropPlatSit(objtype *ob);
+void T_DropPlatFall(objtype *ob);
+void T_DropPlatRise(objtype *ob);
+
+extern statetype s_statplat;
+
+void SpawnStaticPlat(Uint16 tileX, Uint16 tileY);
+
+extern statetype s_goplat;
+extern statetype s_slotgoplat1;
+extern statetype s_slotgoplat2;
+
+void SpawnGoPlat(Uint16 tileX, Uint16 tileY, Sint16 dir, Sint16 type);
+void T_GoPlat(objtype *ob);
+void T_GoSlotPlat(objtype *ob);
+
+extern statetype s_volte1;
+extern statetype s_volte2;
+extern statetype s_volte3;
+extern statetype s_volte4;
+extern statetype s_voltestun;
+
+void SpawnVolte(Uint16 tileX, Uint16 tileY);
+void T_Volte(objtype *ob);
+void C_Volte(objtype *ob, objtype *hit);
+
+extern statetype s_sneakplatsit;
+extern statetype s_sneakplatdodge;
+extern statetype s_sneakplatreturn;
+
+void SpawnSneakPlat(Uint16 tileX, Uint16 tileY);
+void T_SneakPlat(objtype *ob);
+
+extern statetype s_cannon;
+extern statetype s_cannonfire;
+extern statetype s_cshot1;
+extern statetype s_cshot2;
+extern statetype s_cshot3;
+extern statetype s_cshot4;
+extern statetype s_cshothit1;
+extern statetype s_cshothit2;
+
+void SpawnCannon(Uint16 tileX, Uint16 tileY, Sint16 dir);
+void T_Cannon(objtype *ob);
+void C_CShot(objtype *ob, objtype *hit);
+void R_CShot(objtype *ob);
+
+/*
+=============================================================================
+
+						K5_ACT2 DEFINITIONS
+
+=============================================================================
+*/
+
+extern statetype s_sparkywalk1;
+extern statetype s_sparkywalk2;
+extern statetype s_sparkywalk3;
+extern statetype s_sparkywalk4;
+extern statetype s_sparkylook1;
+extern statetype s_sparkylook2;
+extern statetype s_sparkylook3;
+extern statetype s_sparkylook4;
+extern statetype s_sparkylook5;
+extern statetype s_sparkylook6;
+extern statetype s_sparkylook7;
+extern statetype s_sparkylook8;
+extern statetype s_sparkyspeed1;
+extern statetype s_sparkyspeed2;
+extern statetype s_sparkyspeed3;
+extern statetype s_sparkyspeed4;
+extern statetype s_sparkycharge1;
+extern statetype s_sparkycharge2;
+extern statetype s_sparkycharge3;
+extern statetype s_sparkycharge4;
+extern statetype s_sparkyturn1;
+extern statetype s_sparkyturn2;
+extern statetype s_sparkyturn3;
+extern statetype s_sparkystun;
+
+void SpawnSparky(Uint16 tileX, Uint16 tileY);
+void T_Sparky(objtype *ob);
+void T_ChargeCount(objtype *ob);
+void T_SparkyLookL(objtype *ob);
+void T_SparkyLookR(objtype *ob);
+void T_RunSnd1(objtype *ob);
+void T_RunSnd2(objtype *ob);
+void C_Sparky(objtype *ob, objtype *hit);
+void R_Sparky(objtype *ob);
+
+extern statetype s_amptonwalk1;
+extern statetype s_amptonwalk2;
+extern statetype s_amptonwalk3;
+extern statetype s_amptonwalk4;
+extern statetype s_amptonturn;
+extern statetype s_amptongrab1;
+extern statetype s_amptongrab2;
+extern statetype s_amptonclimb;
+extern statetype s_amptonrelease1;
+extern statetype s_amptonrelease2;
+extern statetype s_amptonfiddle1;
+extern statetype s_amptonfiddle2;
+extern statetype s_amptonfiddle3;
+extern statetype s_amptonfiddle4;
+extern statetype s_amptonfiddle5;
+extern statetype s_amptonstun;
+
+void SpawnAmpton(Uint16 tileX, Uint16 tileY);
+void T_Ampton(objtype *ob);
+void T_AmptonClimb(objtype *ob);
+void T_SetNoThink(objtype *ob);
+void C_Ampton(objtype *ob, objtype *hit);
+void R_Ampton(objtype *ob);
+
+extern statetype s_slicestarslide;
+extern statetype s_slicestarbounce;
+extern statetype s_slicestarboom;
+
+void SpawnSlicestarSlide(Uint16 tileX, Uint16 tileY, Sint16 dir);
+void SpawnSlicestarBounce(Uint16 tileX, Uint16 tileY);
+void C_Slicestar(objtype *ob, objtype *hit);
+void R_Slicestar(objtype *ob);
+
+extern statetype s_shellywalk1;
+extern statetype s_shellywalk2;
+extern statetype s_shellywalk3;
+extern statetype s_shellywalk4;
+extern statetype s_shellylook;
+extern statetype s_shellylook2;
+extern statetype s_shellyjump1;
+extern statetype s_shellyjump2;
+extern statetype s_shellydie;
+extern statetype s_shellydieup;
+extern statetype s_shellyboom1;
+extern statetype s_shellyboom2;
+extern statetype s_shellyboom3;
+extern statetype s_shellyboom4;
+extern statetype s_shellypiece1;
+extern statetype s_shellypiece2;
+
+void SpawnShelly(Uint16 tileX, Uint16 tileY);
+void T_ShellyLook(objtype *ob);
+void T_Turn(objtype *ob);
+void T_ShellyFrag(objtype *ob);
+void C_Shelly(objtype *ob, objtype *hit);
+void R_Shelly(objtype *ob);
+void R_Shell(objtype *ob);
+
+/*
+=============================================================================
+
+						K5_ACT3 DEFINITIONS
+
+=============================================================================
+*/
+
+extern statetype s_mine;
+extern statetype s_minecenter;
+extern statetype s_mineshift;
+extern statetype s_mineboom1;
+extern statetype s_mineboom2;
+extern statetype s_mineboom3;
+extern statetype s_mineboom4;
+extern statetype s_mineboom5;
+extern statetype s_mineboom6;
+extern statetype s_minepiece;
+
+void SpawnMine(Uint16 tileX, Uint16 tileY);
+boolean MinePosCheck(Uint16 tileX, Uint16 tileY);
+boolean Walk(objtype *ob, Sint16 dir);
+void ChaseThink(objtype *ob);
+void T_Mine(objtype *ob);
+void C_Solid(objtype *ob, objtype *hit);
+void C_MineFrag(objtype *ob, objtype *hit);
+void T_MineCenter(objtype *ob);
+void T_MineShift(objtype *ob);
+void T_MineFrag(objtype *ob);
+void R_Mine(objtype *ob);
+
+extern statetype s_robored;
+extern statetype s_roboredfire0;
+extern statetype s_roboredfire1;
+extern statetype s_roboredfire2;
+extern statetype s_rshot1;
+extern statetype s_rshot2;
+extern statetype s_rshothit1;
+extern statetype s_rshothit2;
+
+void SpawnRoboRed(Uint16 tileX, Uint16 tileY);
+void T_RoboRed(objtype *ob);
+void C_RoboRed(objtype *ob, objtype *hit);
+void T_RoboShoot(objtype *ob);
+void C_RShot(objtype *ob, objtype *hit);
+void R_RShot(objtype *ob);
+
+extern statetype s_gripsitd;
+extern statetype s_gripjumpd;
+extern statetype s_gripsitl;
+extern statetype s_gripjumpl;
+extern statetype s_gripsitr;
+extern statetype s_gripjumpr;
+extern statetype s_gripsitu;
+extern statetype s_gripjumpu;
+extern statetype s_gripspin1;
+extern statetype s_gripspin2;
+extern statetype s_gripspin3;
+extern statetype s_gripspin4;
+extern statetype s_gripspin5;
+extern statetype s_gripspin6;
+extern statetype s_gripspin7;
+extern statetype s_gripspin8;
+extern statetype s_gripflyd;
+extern statetype s_gripflyl;
+extern statetype s_gripflyr;
+extern statetype s_gripflyu;
+
+void SpawnSpirogrip(Uint16 tileX, Uint16 tileY);
+void T_SpiroLaunch(objtype *ob);
+void R_SpiroFly(objtype *ob);
+
+extern statetype s_spindred1;
+extern statetype s_spindred2;
+extern statetype s_spindred3;
+extern statetype s_spindred4;
+
+void SpawnSpindread(Uint16 tileX, Uint16 tileY);
+void T_Spindread(objtype *ob);
+void C_Spindread(objtype *ob, objtype *hit);
+void R_Spindread(objtype *ob);
+
+extern statetype s_master1;
+extern statetype s_master2;
+extern statetype s_master3;
+extern statetype s_master4;
+extern statetype s_mastershoot1;
+extern statetype s_mastershoot2;
+extern statetype s_mastertport1;
+extern statetype s_mastertport2;
+extern statetype s_mastertport3;
+extern statetype s_mastertport4;
+extern statetype s_mshot1;
+extern statetype s_mshot2;
+extern statetype s_mshot3;
+extern statetype s_mshot4;
+extern statetype s_mspray1;
+extern statetype s_mspray2;
+extern statetype s_mspray3;
+extern statetype s_mspray4;
+
+void SpawnMaster(Uint16 tileX, Uint16 tileY);
+void T_Master(objtype *ob);
+void T_MasterShoot(objtype *ob);
+void C_Master(objtype *ob, objtype *hit);
+void T_MasterTPort(objtype *ob);
+void C_MShot(objtype *ob, objtype *hit);
+void R_MShot(objtype *ob);
+void R_MSpray(objtype *ob);
+
+extern statetype s_shikadi1;
+extern statetype s_shikadi2;
+extern statetype s_shikadi3;
+extern statetype s_shikadi4;
+extern statetype s_shikadiwalk1;
+extern statetype s_shikadiwalk2;
+extern statetype s_shikadiwalk3;
+extern statetype s_shikadiwalk4;
+extern statetype s_shikadigrab;
+extern statetype s_shikadigrab2;
+extern statetype s_shikadistun;
+extern statetype s_polespark1;
+extern statetype s_polespark2;
+
+void SpawnShikadi(Uint16 tileX, Uint16 tileY);
+void T_Shikadi(objtype *ob);
+void C_Shikadi(objtype *ob, objtype *hit);
+void T_PoleShock(objtype *ob);
+void T_PoleSpark(objtype *ob);
+void R_Shikadi(objtype *ob);
+
+extern statetype s_petsit1;
+extern statetype s_petsit2;
+extern statetype s_petbark1;
+extern statetype s_petbark2;
+extern statetype s_pet1;
+extern statetype s_pet2;
+extern statetype s_pet3;
+extern statetype s_pet4;
+extern statetype s_petjump;
+extern statetype s_pshot1;
+extern statetype s_pshot2;
+extern statetype s_pshothot1;
+extern statetype s_pshothot2;
+extern statetype s_petstun;
+
+void SpawnPet(Uint16 tileX, Uint16 tileY);
+void T_Pet(objtype *ob);
+void T_PetSit(objtype *ob);
+void T_PetBark(objtype *ob);
+void C_Pet(objtype *ob, objtype *hit);
+void R_Pet(objtype *ob);
+void R_PetJump(objtype *ob);
+void C_PShot(objtype *ob, objtype *hit);
+void R_PShot(objtype *ob);
+
+extern statetype s_sphereful1;
+extern statetype s_sphereful2;
+extern statetype s_sphereful3;
+extern statetype s_sphereful4;
+
+void SpawnSphereful(Uint16 tileX, Uint16 tileY);
+void T_Sphereful(objtype *ob);
+void R_Sphereful(objtype *ob);
+
+extern statetype s_scottie1;
+extern statetype s_scottie2;
+extern statetype s_scottie3;
+extern statetype s_scottie4;
+extern statetype s_scottieface;
+extern statetype s_scottiestun;
+
+void SpawnScottie(Uint16 tileX, Uint16 tileY);
+void T_Scottie(objtype *ob);
+void C_Scottie(objtype *ob, objtype *hit);
+
+extern statetype s_qed;
+
+void SpawnQed(Uint16 tileX, Uint16 tileY);
+
+#endif
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/KEEN5/K5_SPEC.C b/16/keen456/KEEN4-6/KEEN5/K5_SPEC.C
new file mode 100755
index 00000000..4248954f
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN5/K5_SPEC.C
@@ -0,0 +1,1158 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+/*
+K5_SPEC.C
+=========
+
+Contains (in this order):
+
+- lump definition
+- "Star Wars" crawl text
+- level names & messages
+- Airlock opening & closing code
+- ScanInfoPlane() - for spawning the level objects and marking required sprites
+- game over animation
+- messages for breaking fuses
+*/
+
+#include "CK_DEF.H"
+
+enum {
+	HELP_LUMP,        //  0
+	CONTROLS_LUMP,    //  1
+	KEENTALK_LUMP,    //  2
+	LOADING_LUMP,     //  3
+	PADDLE_LUMP,      //  4
+	KEEN_LUMP,        //  5
+	SUGAR1_LUMP,      //  6
+	SUGAR2_LUMP,      //  7
+	SUGAR3_LUMP,      //  8
+	SUGAR4_LUMP,      //  9
+	SUGAR5_LUMP,      // 10
+	SUGAR6_LUMP,      // 11
+	ONEUP_LUMP,       // 12
+	KEYGEM_LUMP,      // 13
+	AMMO_LUMP,        // 14
+	LASER_LUMP,       // 15
+	WORLDKEEN_LUMP,   // 16
+	MASTER_LUMP,      // 17
+	SHIKADI_LUMP,     // 18
+	SHOCKSHUND_LUMP,  // 19
+	SPHEREFUL_LUMP,   // 20
+	SPARKY_LUMP,      // 21
+	MINE_LUMP,        // 22
+	SLICESTAR_LUMP,   // 23
+	ROBORED_LUMP,     // 24
+	SPIRO_LUMP,       // 25
+	AMPTON_LUMP,      // 26
+	VOLTE_LUMP,       // 27
+	SLOTPLAT_LUMP,    // 28
+	SPINDRED_LUMP,    // 29
+	SHELLEY_LUMP,     // 30
+	PLATFORM_LUMP,    // 31
+	SMALLPLAT_LUMP,   // 32
+	KEYCARD_LUMP,     // 33
+	SCOTTIE_LUMP,     // 34
+	FUSE_LUMP,        // 35
+	STAREXPLODE_LUMP, // 36
+	TELEPORT_LUMP,    // 37
+
+	NUMLUMPS=42       // Keen 5 has 4 unused lumps at the end
+};
+
+Uint16 lumpstart[NUMLUMPS] = {
+	HELP_LUMP_START,
+	CONTROLS_LUMP_START,
+	KEENTALK_LUMP_START,
+	LOADING_LUMP_START,
+	PADDLE_LUMP_START,
+	KEEN_LUMP_START,
+	SUGAR1_LUMP_START,
+	SUGAR2_LUMP_START,
+	SUGAR3_LUMP_START,
+	SUGAR4_LUMP_START,
+	SUGAR5_LUMP_START,
+	SUGAR6_LUMP_START,
+	ONEUP_LUMP_START,
+	KEYGEM_LUMP_START,
+	AMMO_LUMP_START,
+	LASER_LUMP_START,
+	WORLDKEEN_LUMP_START,
+	MASTER_LUMP_START,
+	SHIKADI_LUMP_START,
+	SHOCKSHUND_LUMP_START,
+	SPHEREFUL_LUMP_START,
+	SPARKY_LUMP_START,
+	MINE_LUMP_START,
+	SLICESTAR_LUMP_START,
+	ROBORED_LUMP_START,
+	SPIRO_LUMP_START,
+	AMPTON_LUMP_START,
+	VOLTE_LUMP_START,
+	SLOTPLAT_LUMP_START,
+	SPINDRED_LUMP_START,
+	SHELLEY_LUMP_START,
+	PLATFORM_LUMP_START,
+	MINIPLAT_LUMP_START,
+	KEYCARD_LUMP_START,
+	SCOTTIE_LUMP_START,
+	FUSE_LUMP_START,
+	STAREXPLODE_LUMP_START,
+	TELEPORT_LUMP_START
+};
+
+Uint16 lumpend[NUMLUMPS] = {
+	HELP_LUMP_END,
+	CONTROLS_LUMP_END,
+	KEENTALK_LUMP_END,
+	LOADING_LUMP_END,
+	PADDLE_LUMP_END,
+	KEEN_LUMP_END,
+	SUGAR1_LUMP_END,
+	SUGAR2_LUMP_END,
+	SUGAR3_LUMP_END,
+	SUGAR4_LUMP_END,
+	SUGAR5_LUMP_END,
+	SUGAR6_LUMP_END,
+	ONEUP_LUMP_END,
+	KEYGEM_LUMP_END,
+	AMMO_LUMP_END,
+	LASER_LUMP_END,
+	WORLDKEEN_LUMP_END,
+	MASTER_LUMP_END,
+	SHIKADI_LUMP_END,
+	SHOCKSHUND_LUMP_END,
+	SPHEREFUL_LUMP_END,
+	SPARKY_LUMP_END,
+	MINE_LUMP_END,
+	SLICESTAR_LUMP_END,
+	ROBORED_LUMP_END,
+	SPIRO_LUMP_END,
+	AMPTON_LUMP_END,
+	VOLTE_LUMP_END,
+	SLOTPLAT_LUMP_END,
+	SPINDRED_LUMP_END,
+	SHELLEY_LUMP_END,
+	PLATFORM_LUMP_END,
+	MINIPLAT_LUMP_END,
+	KEYCARD_LUMP_END,
+	SCOTTIE_LUMP_END,
+	FUSE_LUMP_END,
+	STAREXPLODE_LUMP_END,
+	TELEPORT_LUMP_END
+};
+
+boolean lumpneeded[NUMLUMPS];
+
+#if GRMODE == EGAGR
+
+char far swtext[] =
+	"Episode Five\n"
+	"\n"
+	"The Armageddon Machine\n"
+	"\n"
+	"After learning the\n"
+	"location of the secret\n"
+	"Shikadi base, Keen\n"
+	"jumped in the trusty\n"
+	"Bean-with-Bacon\n"
+	"Megarocket and blasted\n"
+	"across interstellar\n"
+	"space.\n"
+	"\n"
+	"Seventy-five furious\n"
+	"games of Paddle War\n"
+	"later, Keen dropped\n"
+	"out of lightspeed near\n"
+	" the Korath system.\n"
+	"\n"
+	"He flew toward the\n"
+	"planet, keeping it\n"
+	"between him and the\n"
+	"base.\n"
+	"\n"
+	"Pulling up underside\n"
+	"and docking at the\n"
+	"Ion Ventilation System,\n"
+	"Keen must destroy the\n"
+	"Shikadi Armageddon\n"
+	"Machine before it\n"
+	"explodes and destroys\n"
+	"the Milky Way!  He\n"
+	"steps into the dark\n"
+	"ventilation duct and\n"
+	"begins his most\n"
+	"dangerous adventure\n"
+	"yet...\n";
+
+#endif
+
+char far l0n[] = "Omegamatic";
+char far l1n[] = "Ion Ventilation System";
+char far l2n[] = "Security Center";
+char far l3n[] = "Defense Tunnel Vlook";
+char far l4n[] = "Energy Flow Systems";
+char far l5n[] = "Defense Tunnel Burrh";
+char far l6n[] = "Regulation\nControl Center";
+char far l7n[] = "Defense Tunnel Sorra";
+char far l8n[] = "Neutrino\nBurst Injector";
+char far l9n[] = "Defense Tunnel Teln";
+char far l10n[] = "Brownian\nMotion Inducer";
+char far l11n[] = "Gravitational\nDamping Hub";
+char far l12n[] = "Quantum\nExplosion Dynamo";
+char far l13n[] = "Korath III Base";
+char far l14n[] = "BWBMegarocket";
+char far l15n[] = "High Scores";
+
+char far l0e[] = "Keen purposefully\nwanders about the\nOmegamatic";
+char far l1e[] = "Keen investigates the\nIon Ventilation System";
+char far l2e[] = "Keen struts through\nthe Security Center";
+char far l3e[] = "Keen invades\nDefense Tunnel Vlook";
+char far l4e[] = "Keen engages\nEnergy Flow Systems";
+char far l5e[] = "Keen barrels into\nDefense Tunnel Burrh";
+char far l6e[] = "Keen goes nuts in\nthe Regulation\nControl Center";
+char far l7e[] = "Keen regrets entering\nDefense Tunnel Sorra";
+char far l8e[] = "Keen blows through\nthe Neutrino\nBurst Injector";
+char far l9e[] = "Keen trots through\nDefense Tunnel Teln";
+char far l10e[] = "Keen breaks into\nthe Brownian\nMotion Inducer";
+char far l11e[] = "Keen hurries through\nthe Gravitational\nDamping Hub";
+char far l12e[] = "Keen explodes into\nthe Quantum\nExplosion Dynamo";
+char far l13e[] = "Keen faces danger\nin the secret\nKorath III Base";
+char far l14e[] = "Keen will not be\nin the BWBMegarocket";
+char far l15e[] = "Keen unexplainedly\nfinds himself by\ntheHigh Scores";	// sic!
+
+char far *levelnames[GAMELEVELS] = {
+	l0n,
+	l1n,
+	l2n,
+	l3n,
+	l4n,
+	l5n,
+	l6n,
+	l7n,
+	l8n,
+	l9n,
+	l10n,
+	l11n,
+	l12n,
+	l13n,
+	l14n,
+	l15n
+};
+
+char far *levelenter[GAMELEVELS] = {
+	l0e,
+	l1e,
+	l2e,
+	l3e,
+	l4e,
+	l5e,
+	l6e,
+	l7e,
+	l8e,
+	l9e,
+	l10e,
+	l11e,
+	l12e,
+	l13e,
+	l14e,
+	l15e
+};
+
+Uint16 bonuslump[] = {
+	KEYGEM_LUMP, KEYGEM_LUMP, KEYGEM_LUMP, KEYGEM_LUMP,
+	SUGAR1_LUMP, SUGAR2_LUMP, SUGAR3_LUMP,
+	SUGAR4_LUMP, SUGAR5_LUMP, SUGAR6_LUMP,
+	ONEUP_LUMP, AMMO_LUMP, KEYCARD_LUMP, 0, 0
+};
+
+//============================================================================
+
+/*
+===========================
+=
+= OpenMapDoor
+=
+===========================
+*/
+
+void OpenMapDoor(Sint16 tileX, Sint16 tileY)
+{
+	Sint16 x, y;
+	Uint16 tiles[2][2];
+
+	for (y=0; y<2; y++)
+	{
+		for (x=0; x<2; x++)
+		{
+			tiles[y][x] = *(mapsegs[1]+mapbwidthtable[y]/2 + x + 10);
+		}
+	}
+	RF_MemToMap(&tiles[0][0], 1, tileX, tileY, 2, 2);
+}
+
+/*
+===========================
+=
+= CloseMapDoor
+=
+===========================
+*/
+
+void CloseMapDoor(Sint16 tileX, Sint16 tileY)
+{
+	Sint16 x, y;
+	Uint16 tiles[2][2];
+
+	for (y=0; y<2; y++)
+	{
+		for (x=0; x<2; x++)
+		{
+			tiles[y][x] = *(mapsegs[1]+mapbwidthtable[y]/2 + x);
+		}
+	}
+	RF_MemToMap(&tiles[0][0], 1, tileX, tileY, 2, 2);
+}
+
+//============================================================================
+
+/*
+==========================
+=
+= ScanInfoPlane
+=
+= Spawn all actors and mark down special places
+=
+==========================
+*/
+
+void ScanInfoPlane(void)
+{
+	Uint16 i, x, y, chunk;
+	Sint16 info;
+	Uint16 far *map;
+	objtype *ob;
+
+	InitObjArray();                  // start spawning things with a clean slate
+
+	memset(lumpneeded, 0, sizeof(lumpneeded));
+	gamestate.numfuses = 0;
+
+	map = mapsegs[2];
+
+	for (y=0; y<mapheight; y++)
+	{
+		for (x=0; x<mapwidth; x++)
+		{
+			info = *map++;
+
+			if (info == 0)
+				continue;
+
+			switch (info)
+			{
+			case 1:
+				SpawnKeen(x, y, 1);
+				SpawnScore();
+				lumpneeded[KEEN_LUMP] = true;
+				CA_MarkGrChunk(SCOREBOXSPR);
+				break;
+
+			case 2:
+				SpawnKeen(x, y, -1);
+				SpawnScore();
+				lumpneeded[KEEN_LUMP] = true;
+				CA_MarkGrChunk(SCOREBOXSPR);
+				break;
+
+			case 3:
+				SpawnScore();
+				lumpneeded[WORLDKEEN_LUMP] = true;
+				CA_MarkGrChunk(SCOREBOXSPR);
+				if (playstate == ex_portout)
+					break;
+				SpawnWorldKeen(x, y);
+				break;
+
+			case 26:
+				if (playstate != ex_portout)
+					break;
+				SpawnWorldKeenPort(x, y);
+				break;
+
+			case 6:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 5:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 4:
+				SpawnSparky(x, y);
+				lumpneeded[SPARKY_LUMP] = true;
+				break;
+
+			case 9:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 8:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 7:
+				SpawnMine(x, y);
+				lumpneeded[MINE_LUMP] = true;
+				break;
+
+			case 12:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 11:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 10:
+				SpawnSlicestarSlide(x, y, 0);
+				lumpneeded[SLICESTAR_LUMP] = true;
+				break;
+
+			case 15:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 14:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 13:
+				SpawnRoboRed(x, y);
+				lumpneeded[ROBORED_LUMP] = true;
+				break;
+
+			case 18:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 17:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 16:
+				SpawnSpirogrip(x, y);
+				lumpneeded[SPIRO_LUMP] = true;
+				break;
+
+			case 21:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 20:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 19:
+				SpawnSlicestarBounce(x, y);
+				lumpneeded[SLICESTAR_LUMP] = true;
+				break;
+
+			case 24:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 23:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 22:
+				SpawnSlicestarSlide(x, y, 1);
+				lumpneeded[SLICESTAR_LUMP] = true;
+				break;
+
+			case 25:
+				RF_SetScrollBlock(x, y, true);
+				break;
+
+			// case 26 (teleported map keen) is handled above
+
+			case 27:
+			case 28:
+			case 29:
+			case 30:
+				SpawnPlatform(x, y, info-27, 0);
+				lumpneeded[PLATFORM_LUMP] = true;
+				break;
+
+			// case 31 is the block icon
+
+			case 32:
+				SpawnDropPlat(x, y);
+				lumpneeded[PLATFORM_LUMP] = true;
+				break;
+
+			case 35:
+				SpawnStaticPlat(x, y);
+				lumpneeded[PLATFORM_LUMP] = true;
+				break;
+			case 34:
+				if (gamestate.difficulty > gd_Normal)
+					break;
+				SpawnStaticPlat(x, y);
+				lumpneeded[PLATFORM_LUMP] = true;
+				break;
+			case 33:
+				if (gamestate.difficulty > gd_Easy)
+					break;
+				SpawnStaticPlat(x, y);
+				lumpneeded[PLATFORM_LUMP] = true;
+				break;
+
+			case 36:
+			case 37:
+			case 38:
+			case 39:
+				SpawnGoPlat(x, y, info-36, 0);
+				lumpneeded[PLATFORM_LUMP] = true;
+				break;
+
+			case 40:
+				SpawnSneakPlat(x, y);
+				lumpneeded[PLATFORM_LUMP] = true;
+				break;
+
+			case 41:
+				if (gamestate.mapon == 12)
+				{
+					gamestate.numfuses = 4;
+					SpawnQed(x, y);
+				}
+				else
+				{
+					gamestate.numfuses++;
+				}
+				lumpneeded[FUSE_LUMP] = true;
+				break;
+
+			case 44:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 43:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 42:
+				SpawnAmpton(x, y);
+				lumpneeded[AMPTON_LUMP] = true;
+				break;
+
+			case 53:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 49:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 45:
+				SpawnCannon(x, y, 0);
+				lumpneeded[LASER_LUMP] = true;
+				break;
+
+			case 54:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 50:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 46:
+				SpawnCannon(x, y, 1);
+				lumpneeded[LASER_LUMP] = true;
+				break;
+
+			case 55:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 51:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 47:
+				SpawnCannon(x, y, 2);
+				lumpneeded[LASER_LUMP] = true;
+				break;
+
+			case 56:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 52:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 48:
+				SpawnCannon(x, y, 3);
+				lumpneeded[LASER_LUMP] = true;
+				break;
+
+			case 69:
+				if (gamestate.ammo >= 5)
+					break;
+				info = 68;	// spawn ammo
+				//no break here!
+			case 57:
+			case 58:
+			case 59:
+			case 60:
+			case 61:
+			case 62:
+			case 63:
+			case 64:
+			case 65:
+			case 66:
+			case 67:
+			case 68:
+				SpawnBonus(x, y, info-57);
+				lumpneeded[bonuslump[info-57]] = true;
+				break;
+			case 70:
+				SpawnBonus(x, y, info-58);
+				lumpneeded[bonuslump[info-58]] = true;
+				break;
+
+			case 73:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 72:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 71:
+				SpawnVolte(x, y);
+				lumpneeded[VOLTE_LUMP] = true;
+				break;
+
+			case 76:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 75:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 74:
+				SpawnShelly(x, y);
+				lumpneeded[SHELLEY_LUMP] = true;
+				break;
+
+			case 79:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 78:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 77:
+				SpawnSpindread(x, y);
+				lumpneeded[SPINDRED_LUMP] = true;
+				break;
+
+			case 80:
+			case 81:
+			case 82:
+			case 83:
+				SpawnGoPlat(x, y, info-80, 1);
+				lumpneeded[SLOTPLAT_LUMP] = true;
+				break;
+
+			case 84:
+			case 85:
+			case 86:
+			case 87:
+				SpawnPlatform(x, y, info-84, 1);
+				lumpneeded[SLOTPLAT_LUMP] = true;
+				break;
+
+			case 90:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 89:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 88:
+				SpawnMaster(x, y);
+				lumpneeded[MASTER_LUMP] = true;
+				break;
+
+			// cases 91 to 98 are direction arrows
+
+			case 101:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 100:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 99:
+				SpawnShikadi(x, y);
+				lumpneeded[SHIKADI_LUMP] = true;
+				break;
+
+			case 104:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 103:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 102:
+				SpawnPet(x, y);
+				lumpneeded[SHOCKSHUND_LUMP] = true;
+				break;
+
+			case 107:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 106:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 105:
+				SpawnSphereful(x, y);
+				lumpneeded[SPHEREFUL_LUMP] = true;
+				break;
+
+			// cases 108 to 123 are wall collision icons for the WallDebug cheat
+
+			case 124:
+				SpawnScottie(x, y);
+				lumpneeded[SCOTTIE_LUMP] = true;
+				break;
+
+			case 125:
+				lumpneeded[TELEPORT_LUMP] = true;
+
+			}
+		}
+	}
+
+	for (ob = player; ob; ob = ob->next)
+	{
+		if (ob->active != ac_allways)
+			ob->active = ac_no;
+	}
+
+	for (i = 0; i < NUMLUMPS; i++)
+	{
+		if (lumpneeded[i])
+		{
+			for (chunk = lumpstart[i]; chunk <= lumpend[i]; chunk++)
+			{
+				CA_MarkGrChunk(chunk);
+			}
+		}
+	}
+
+	// Keen 5 addition to PatchWorldMap (PatchWorldMap is shared across Keen 4-6)
+	if (gamestate.mapon == 0)
+	{
+		info = CONVERT_GLOBAL_TO_TILE(player->y);
+		if (info < 75 || info > 100)
+		{
+			CloseMapDoor(24, 76);
+			OpenMapDoor(22, 55);
+		}
+		if (gamestate.leveldone[4] && gamestate.leveldone[6] && gamestate.leveldone[8] && gamestate.leveldone[10]
+			&& (info > 39 || info > 100) )
+		{
+			OpenMapDoor(26, 55);
+		}
+		if (info <= 39 || info > 100)
+		{
+			OpenMapDoor(24, 30);
+		}
+	}
+}
+
+/*
+=============================================================================
+
+						  GAME OVER SEQUENCE
+
+=============================================================================
+*/
+
+/*
+------------------------------------------------------------------------------
+The galaxy explosion chunk contains data in the following format:
+
+struct {
+	Uint16 posx[4000];
+	Uint16 velx[4000];
+	Uint16 posy[4000];
+	Uint16 vely[4000];
+};
+
+The values are stored as "fixed point" numbers (divide each number by 128 to
+get the amount in pixel units). The code in MoveStars basically does the
+following:
+
+1.	set all pixels on the screen to black
+
+2.	for each of the 4000 entries do:
+
+2.1	x := posx[i] + velx[i]
+
+2.2	if x (in pixels) is < 0 or > 320 then go to 2.8
+
+2.3	posx[i] := x
+
+2.4	y := posy[i] + vely[i]
+
+2.5	if y (in pixels) is < 0 or > 200 then go to 2.8
+
+2.6	posy[i] := y
+
+2.7	draw a white pixel at position (x, y) on the screen
+
+2.8	continue with the next entry
+
+------------------------------------------------------------------------------
+*/
+
+#if GRMODE == CGAGR
+
+Uint8 plotpixels[8] = {0xC0, 0x30, 0x0C, 0x03};
+
+/*
+===========================
+=
+= MoveStars   CGA
+=
+===========================
+*/
+
+void MoveStars(void)
+{
+	asm {
+		mov	ax, screenseg;
+		mov	es, ax;
+		mov	ds, word ptr grsegs + 2*GALAXY;
+		mov	cx, 2000h;
+		xor	ax, ax;
+		xor	di, di;
+		rep stosw;
+		mov	si, 7998;
+	}
+l1:
+	asm {
+		mov	ax, [si];		// get posx
+		add	ax, [si+8000];		// add velx
+		cmp	ax, 40960;		// check if new posx is on screen
+		ja 	l2;
+		mov	[si], ax;		// set new posx
+		mov	bx, [si+16000];		// get posy
+		add	bx, [si+24000];		// add vely
+		cmp	bx, 25600;		// check if new posy is on screen
+		ja 	l2;
+		mov	[si+16000], bx;		// set new posy
+		mov	cl, 7;
+		shr	bx, cl;
+		shl	bx, 1;
+		mov	di, word ptr ss:ylookup[bx];
+		mov	bx, ax;
+		mov	cl, 9;
+		shr	ax, cl;
+		add	di, ax;
+		mov	cl, 7;
+		shr	bx, cl;
+		and	bx, 3;
+		mov	al, BYTE PTR ss:plotpixels[bx];
+		or		es:[di], al;		// draw the pixel
+	}
+l2:
+	asm {
+		sub	si, 2;
+		jns	l1;
+		mov	ax, ss;
+		mov	ds, ax;
+	}
+}
+
+/*
+===========================
+=
+= GameOver   CGA
+=
+===========================
+*/
+
+void GameOver(void)
+{
+	Sint16 i;
+
+	FreeGraphics();
+	CA_CacheGrChunk(MILKYWAYPIC);
+	CA_CacheGrChunk(GALAXY);
+	CA_CacheGrChunk(GAMEOVERPIC);
+	RF_FixOfs();
+	VW_ClearVideo(BLACK);
+	VWB_DrawPic(0, 0, MILKYWAYPIC);
+	VW_UpdateScreen();
+
+	SD_WaitSoundDone();
+	SD_PlaySound(SND_GAMEOVER2);
+	SD_WaitSoundDone();
+	SD_PlaySound(SND_GAMEOVER1);
+
+	IN_ClearKeysDown();
+	VW_SetLineWidth(80);
+
+	for (i=0; i<60; i++)
+	{
+		lasttimecount = TimeCount;
+		MoveStars();
+		VW_UpdateScreen();
+
+		do {} while (TimeCount-lasttimecount < 4);
+
+		if (LastScan)
+			break;
+	}
+
+	VW_SetLineWidth(SCREENWIDTH);
+	VW_ClearVideo(BLACK);
+	StartMusic(18);
+	VWB_DrawPic(32, 80, GAMEOVERPIC);
+	VW_UpdateScreen();
+	IN_UserInput(24*TickBase, false);
+	StopMusic();
+}
+
+//============================================================================
+
+#else
+
+Uint16 dim[18] = {8, 8, 7, 15, 7, 8, 0, 8, 7, 15, 7, 8, 0, 0, 0, 0, 0, 0};
+Uint16 bright[18] = {7, 7, 7, 7, 7, 15, 7, 8, 0, 7, 15, 7, 8, 0, 0, 0, 0, 0};
+Uint8 galaxycolors[17] = {0, 1, 2, 3, 4, 5, 6, 7, 0x18, 0x19, 0x1A, 0x1B, 0x1C, 0x1D, 0x1E, 0x1F, 3};
+Uint8 plotpixels[8] = {0x80, 0x40, 0x20, 0x10, 0x08, 0x04, 0x02, 0x01};
+
+/*
+===========================
+=
+= MoveStars   EGA
+=
+===========================
+*/
+
+void MoveStars(Uint16 dest)
+{
+	asm {
+		mov	dx, GC_INDEX;
+		mov	al, GC_BITMASK;
+		out	dx, al;
+		inc	dx;
+		mov	ds, word ptr grsegs + 2*GALAXY;
+		mov	ax, 0A000h;
+		mov	es, ax;
+		mov	cx, 1000h;
+		xor	ax, ax;
+		mov	di, dest;
+		rep stosw;
+		mov	si, 7998;
+	}
+l1:
+	asm {
+		mov	ax, [si];		// get posx
+		add	ax, [si+8000];		// add velx
+		cmp	ax, 40960;		// check if new posx is on screen
+		ja 	l2;
+		mov	[si], ax;		// set new posx
+		mov	bx, [si+16000];		// get posy
+		add	bx, [si+24000];		// add vely
+		cmp	bx, 25600;		// check if new posy is on screen
+		ja 	l2;
+		mov	[si+16000], bx;		// set new posy
+		mov	cl, 7;
+		shr	bx, cl;
+		shl	bx, 1;
+		mov	di, word ptr ss:ylookup[bx];
+		add	di, dest;
+		mov	bx, ax;
+		mov	cl, 10;
+		shr	ax, cl;
+		add	di, ax;
+		mov	cl, 7;
+		shr	bx, cl;
+		and	bx, 7;
+		mov	al, BYTE PTR ss:plotpixels[bx];
+		out	dx, al;
+		mov	al, 0Fh;
+		xchg	al, es:[di];		// draw the pixel
+	}
+l2:
+	asm {
+		sub	si, 2;
+		jns	l1;
+		mov	ax, ss;
+		mov	ds, ax;
+		mov	al, 0FFh;
+		out	dx, al;
+	}
+}
+
+/*
+===========================
+=
+= SetCrtc   EGA
+=
+===========================
+*/
+
+void SetCrtc(Uint16 addr)
+{
+	asm {
+		cli;
+		mov	cx, addr;
+		mov	dx, CRTC_INDEX;
+		mov	al, CRTC_STARTHIGH;
+		out	dx, al;
+		inc	dx;
+		mov	al, ch;
+		out	dx, al;
+		dec	dx;
+		mov	al, CRTC_STARTLOW;
+		out	dx, al;
+		inc	dx;
+		mov	al, cl;
+		out	dx, al;
+		sti;
+	}
+}
+
+/*
+===========================
+=
+= GameOver   EGA
+=
+===========================
+*/
+
+void GameOver(void)
+{
+	Sint16 i;
+
+	FreeGraphics();
+	VW_FadeOut();
+	CA_CacheGrChunk(MILKYWAYPIC);
+	CA_CacheGrChunk(GALAXY);
+	CA_CacheGrChunk(GAMEOVERPIC);
+	VW_SetLineWidth(40);
+	VW_SetScreen(0, 0);
+	bufferofs = 0;
+	VW_ClearVideo(0);
+	VW_DrawPic(0, 0, MILKYWAYPIC);
+	VW_ScreenToScreen(0, 0x2000, 40, 200);
+	VW_FadeIn();
+	IN_ClearKeysDown();
+	SD_PlaySound(SND_GAMEOVER2);
+
+	for (i=0; i<18; i++)
+	{
+		galaxycolors[8] = dim[i];
+		galaxycolors[7] = bright[i];
+
+		SetPalette(galaxycolors);
+
+		VW_WaitVBL(10);
+		if (LastScan)
+			goto gameover;
+	}
+
+	EGAWRITEMODE(2);
+	EGAMAPMASK(15);
+	SD_PlaySound(SND_GAMEOVER1);
+
+	for (i=0; i<30; i++)
+	{
+		lasttimecount = TimeCount;
+		MoveStars(0x2000);
+		SetCrtc(0x2000);
+		do {} while (TimeCount-lasttimecount < 4);
+
+		lasttimecount = TimeCount;
+		MoveStars(0);
+		SetCrtc(0);
+		do {} while (TimeCount-lasttimecount < 4);
+
+		if (LastScan)
+			goto gameover;
+	}
+
+gameover:
+	EGAWRITEMODE(0);
+	VW_ClearVideo(BLACK);
+	VW_SetLineWidth(SCREENWIDTH);
+	VW_SetDefaultColors();
+	RF_FixOfs();
+	StartMusic(18);
+	VWB_DrawPic(32, 80, GAMEOVERPIC);
+	VW_UpdateScreen();
+	IN_UserInput(24*TickBase, false);
+	StopMusic();
+}
+
+#endif
+
+//============================================================================
+
+/*
+===========================
+=
+= FinishedFuse
+=
+===========================
+*/
+
+void FinishedFuse(void)
+{
+	SD_WaitSoundDone();
+	CA_UpLevel();
+#if 0
+	// bugfix:
+	CA_ClearMarks();	// don't cache more than we actually need here
+#endif
+	CA_MarkGrChunk(KEENTALK1PIC);
+	CA_MarkGrChunk(KEENTALK2PIC);
+	CA_CacheMarks(NULL);
+
+	VW_FixRefreshBuffer();
+	US_CenterWindow(26, 8);
+	WindowW -= 48;
+	VWB_DrawPic(WindowX+WindowW, WindowY, KEENTALK1PIC);
+	PrintY += 12;
+	if (gamestate.mapon == 13)
+	{
+		US_CPrint(
+			"I wonder what that\n"
+			"fuse was for....\n"
+			);
+	}
+	else
+	{
+		US_CPrint(
+			"One of the four\n"
+			"machines protecting the\n"
+			"main elevator shaft--\n"
+			"toast!\n"
+			);
+	}
+	VW_UpdateScreen();
+	VW_WaitVBL(30);
+	IN_ClearKeysDown();
+	IN_Ack();
+
+	VWB_DrawPic(WindowX+WindowW, WindowY, KEENTALK2PIC);
+	VW_UpdateScreen();
+	VW_WaitVBL(30);
+	IN_ClearKeysDown();
+	IN_Ack();
+
+	CA_DownLevel();
+	StopMusic();
+}
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/KEEN5C/GFXC_CK5.EQU b/16/keen456/KEEN4-6/KEEN5C/GFXC_CK5.EQU
new file mode 100755
index 00000000..9cb6e6b0
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN5C/GFXC_CK5.EQU
@@ -0,0 +1,55 @@
+;=====================================
+;
+; Graphics .EQU file for .CK5
+; not IGRAB-ed :)
+;
+;=====================================
+
+;INCLUDE "VERSION.EQU"
+
+;
+; Amount of each data item
+;
+NUMFONT     =	2
+NUMFONTM    =	0
+NUMPICM     =	3
+NUMTILE8    =	108
+NUMTILE8M   =	36
+NUMTILE32   =	0
+NUMTILE32M  =	0
+
+;
+; Amount of each item in episode 5
+;
+NUMPICS     =	94
+NUMSPRITES  =	346
+NUMTILE16   =	1512
+NUMTILE16M  =	2952
+NUMEXTERN   =	17
+
+
+;
+; File offsets for data items
+;
+STRUCTPIC       =	0
+STRUCTPICM      =	1
+STRUCTSPRITE    =	2
+
+STARTFONT       =	3
+STARTFONTM      =	(STARTFONT+NUMFONT)
+STARTPICS       =	(STARTFONTM+NUMFONTM)
+STARTPICM       =	(STARTPICS+NUMPICS)
+STARTSPRITES    =	(STARTPICM+NUMPICM)
+STARTTILE8      =	(STARTSPRITES+NUMSPRITES)
+STARTTILE8M     =	(STARTTILE8+1)
+STARTTILE16     =	(STARTTILE8M+1)
+STARTTILE16M    =	(STARTTILE16+NUMTILE16)
+STARTTILE32     =	(STARTTILE16M+NUMTILE16M)
+STARTTILE32M    =	(STARTTILE32+NUMTILE32)
+STARTEXTERN     =	(STARTTILE32M+NUMTILE32M)
+
+NUMCHUNKS       =	(STARTEXTERN+NUMEXTERN)
+
+;
+; Thank you for using IGRAB!
+;
diff --git a/16/keen456/KEEN4-6/KEEN5C/GFXC_CK5.H b/16/keen456/KEEN4-6/KEEN5C/GFXC_CK5.H
new file mode 100755
index 00000000..95d639ed
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN5C/GFXC_CK5.H
@@ -0,0 +1,690 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+#ifndef __GFX_H__
+#define __GFX_H__
+
+//#include "VERSION.H"
+
+//////////////////////////////////////
+//
+// Graphics .H file for .CK5
+// not IGRAB-ed :)
+//
+//////////////////////////////////////
+
+//
+// Lump creation macros
+//
+
+#define START_LUMP(actualname, dummyname) actualname, dummyname=actualname-1,
+#define END_LUMP(actualname, dummyname) dummyname, actualname=dummyname-1,
+
+//
+// Amount of each data item
+//
+
+//common numbers:
+#define NUMCHUNKS    NUMGRCHUNKS
+#define NUMFONT      2
+#define NUMFONTM     0
+#define NUMPICM      3
+#define NUMTILE8     108	// BUG: only 104 tiles exist in EGAGRAPH!
+#define NUMTILE8M    36		// BUG: only 20 tiles exist in EGAGRAPH!
+#define NUMTILE32    0
+#define NUMTILE32M   0
+
+//episode-specific numbers:
+#define NUMPICS      94
+#define NUMSPRITES   346
+#define NUMTILE16    1512
+#define NUMTILE16M   2952
+#define NUMEXTERNS   15
+
+//
+// File offsets for data items
+//
+#define STRUCTPIC    0
+#define STRUCTPICM   1
+#define STRUCTSPRITE 2
+
+#define STARTFONT    3
+#define STARTFONTM   (STARTFONT+NUMFONT)
+#define STARTPICS    (STARTFONTM+NUMFONTM)
+#define STARTPICM    (STARTPICS+NUMPICS)
+#define STARTSPRITES (STARTPICM+NUMPICM)
+#define STARTTILE8   (STARTSPRITES+NUMSPRITES)
+#define STARTTILE8M  (STARTTILE8+1)
+#define STARTTILE16  (STARTTILE8M+1)
+#define STARTTILE16M (STARTTILE16+NUMTILE16)
+#define STARTTILE32  (STARTTILE16M+NUMTILE16M)
+#define STARTTILE32M (STARTTILE32+NUMTILE32)
+#define STARTEXTERNS (STARTTILE32M+NUMTILE32M)
+
+typedef enum {
+	// Lump Start
+
+	LASTFONT=STARTPICS-1,
+
+	PADDINGPIC,                  // 5 (compensate for the missing Star Wars font to give the other pics the correct chunk numbers)
+
+	START_LUMP(HELP_LUMP_START, __HELPSTART)
+	H_HELPPIC,                   // 6
+	H_LARROWPIC,                 // 7
+	H_RARROWPIC,                 // 8
+	H_ESCPIC,                    // 9
+	H_ENTERPIC,                  // 10
+	H_BOTTOMINSTRPIC,            // 11
+	H_GUMPIC,                    // 12
+	H_MARSHMALLOWPIC,            // 13
+	H_CHOCMILKPIC,               // 14
+	H_TARTSTIXPIC,               // 15
+	H_STOOPIESPIC,               // 16
+	H_SUGARPIC,                  // 17
+	H_VITALINPIC,                // 18
+	H_STUNNERPIC,                // 19
+	H_GEMPIC,                    // 20
+	H_KEGPIC,                    // 21
+	H_ENDOFTEXTPIC,              // 22
+	H_HELPMENUPIC,               // 23
+	H_HANDPIC,                   // 24
+	H_ARROWSENTERESCPIC,         // 25
+	H_FLASHARROW1PIC,            // 26
+	H_FLASHARROW2PIC,            // 27
+	H_TOPWINDOWPIC,              // 28
+	H_LEFTWINDOWPIC,             // 29
+	H_RIGHTWINDOWPIC,            // 30
+	H_BOTTOMINFOPIC,             // 31
+	H_BOTTOMWINDOWPIC,           // 32
+	H_BARPIC,                    // 33
+	H_SPARKYPIC,                 // 34
+	H_AMPTONPIC,                 // 35
+	H_SLICESTARPIC,              // 36
+	H_VOLTEFACEPIC,              // 37
+	H_ROBOREDPIC,                // 38
+	H_SHELLEYPIC,                // 39
+	H_SPIROGRIPPIC,              // 40
+	H_MINEPIC,                   // 41
+	H_SPINDREDPIC,               // 42
+	H_SHIKADIPIC,                // 43
+	H_SPHEREFULPIC,              // 44
+	H_PETPIC,                    // 45
+	H_MASTERPIC,                 // 46
+	H_IDLOGOPIC,                 // 47
+	H_STORY1PIC,                 // 48
+	H_STORY2PIC,                 // 49
+	H_STORY3PIC,                 // 50
+	H_STORY4PIC,                 // 51
+	H_VISAPIC,                   // 52
+	H_MCPIC,                     // 53
+	H_KEENTHUMBSUPPIC,           // 54
+	H_END1PIC,                   // 55
+	H_END2PIC,                   // 56
+	H_END3PIC,                   // 57
+	H_END4PIC,                   // 58
+	H_END5PIC,                   // 59
+	H_END6PIC,                   // 60
+	H_END7PIC,                   // 61
+	H_END8PIC,                   // 62
+	H_CONGRATSPIC,               // 63
+	H_KEENFEEDSPIC,              // 64
+	H_DOORCARDPIC,               // 65
+	H_KEEN6PIC,                  // 66
+	END_LUMP(HELP_LUMP_END, __HELPEND)
+
+	START_LUMP(CONTROLS_LUMP_START, __CONTROLSSTART)
+	CP_MAINMENUPIC,              // 67
+	CP_NEWGAMEMENUPIC,           // 68
+	CP_LOADMENUPIC,              // 69
+	CP_SAVEMENUPIC,              // 70
+	CP_CONFIGMENUPIC,            // 71
+	CP_SOUNDMENUPIC,             // 72
+	CP_MUSICMENUPIC,             // 73
+	CP_KEYBOARDMENUPIC,          // 74
+	CP_KEYMOVEMENTPIC,           // 75
+	CP_KEYBUTTONPIC,             // 76
+	CP_JOYSTICKMENUPIC,          // 77
+	CP_OPTIONSMENUPIC,           // 78
+	CP_PADDLEWARPIC,             // 79
+	CP_QUITPIC,                  // 80
+	CP_JOYSTICKPIC,              // 81
+	CP_MENUSCREENPIC,            // 82
+	END_LUMP(CONTROLS_LUMP_END, __COLTROLSEND)
+
+	START_LUMP(_LUMP_START, __START)
+	IDSOFTPIC,                   // 83
+	PROGTEAMPIC,                 // 84
+	ARTISTPIC,                   // 85
+	DIRECTORPIC,                 // 86
+	SW_BACKGROUNDPIC,            // 87
+	TITLEPICPIC,                 // 88
+	MILKYWAYPIC,                 // 89
+	END_LUMP(_LUMP_END, __END)
+
+	START_LUMP(KEENTALK_LUMP_START, __KEENTALKSTART)
+	KEENTALK1PIC,                // 90
+	KEENTALK2PIC,                // 91
+	END_LUMP(KEENTALK_LUMP_END, __KEENTALKEND)
+
+	START_LUMP(LOADING_LUMP_START, __LOADINGSTART)
+	KEENCOUNT1PIC,               // 92
+	KEENCOUNT2PIC,               // 93
+	KEENCOUNT3PIC,               // 94
+	KEENCOUNT4PIC,               // 95
+	KEENCOUNT5PIC,               // 96
+	KEENCOUNT6PIC,               // 97
+	END_LUMP(LOADING_LUMP_END, __LOADINGEND)
+
+	GAMEOVERPIC,                 // 98
+
+	CP_MENUMASKPICM,             // 99
+	CORDPICM,                    // 100
+	METALPOLEPICM,               // 101
+
+	//
+	// SPRITES
+	//
+
+	START_LUMP(PADDLE_LUMP_START, __PADDLESTART)
+	PADDLESPR,                   // 102
+	BALLSPR,                     // 103
+	BALL1PIXELTOTHERIGHTSPR,     // 104
+	BALL2PIXELSTOTHERIGHTSPR,    // 105
+	BALL3PIXELSTOTHERIGHTSPR,    // 106
+	END_LUMP(PADDLE_LUMP_END, __PADDLEEND)
+
+	DEMOPLAQUESPR,               // 107
+
+	START_LUMP(KEEN_LUMP_START, __KEENSTART)
+	KEENSTANDRSPR,               // 108
+	KEENRUNR1SPR,                // 109
+	KEENRUNR2SPR,                // 110
+	KEENRUNR3SPR,                // 111
+	KEENRUNR4SPR,                // 112
+	KEENJUMPR1SPR,               // 113
+	KEENJUMPR2SPR,               // 114
+	KEENJUMPR3SPR,               // 115
+	KEENSTANDLSPR,               // 116
+	KEENRUNL1SPR,                // 117
+	KEENRUNL2SPR,                // 118
+	KEENRUNL3SPR,                // 119
+	KEENRUNL4SPR,                // 120
+	KEENJUMPL1SPR,               // 121
+	KEENJUMPL2SPR,               // 122
+	KEENJUMPL3SPR,               // 123
+	KEENLOOKUSPR,                // 124
+	KEENWAITR1SPR,               // 125
+	KEENWAITR2SPR,               // 126
+	KEENWAITR3SPR,               // 127
+	KEENSITREAD1SPR,             // 128
+	KEENSITREAD2SPR,             // 129
+	KEENSITREAD3SPR,             // 130
+	KEENSITREAD4SPR,             // 131
+	KEENREAD1SPR,                // 132
+	KEENREAD2SPR,                // 133
+	KEENREAD3SPR,                // 134
+	KEENSTOPREAD1SPR,            // 135
+	KEENSTOPREAD2SPR,            // 136
+	KEENLOOKD1SPR,               // 137
+	KEENLOOKD2SPR,               // 138
+	KEENONPLATSPR,               // 139
+	KEENDIE1SPR,                 // 140
+	KEENDIE2SPR,                 // 141
+	KEENSTUNSPR,                 // 142
+	STUNSTARS1SPR,               // 143
+	STUNSTARS2SPR,               // 144
+	STUNSTARS3SPR,               // 145
+	KEENSHOOTLSPR,               // 146
+	KEENJLSHOOTLSPR,             // 147
+	KEENJSHOOTDSPR,              // 148
+	KEENJSHOOTUSPR,              // 149
+	KEENSHOOTUSPR,               // 150
+	KEENSHOOTRSPR,               // 151
+	KEENJRSHOOTRSPR,             // 152
+	STUN1SPR,                    // 153
+	STUN2SPR,                    // 154
+	STUN3SPR,                    // 155
+	STUN4SPR,                    // 156
+	STUNHIT1SPR,                 // 157
+	STUNHIT2SPR,                 // 158
+	KEENSHINNYR1SPR,             // 159
+	KEENSHINNYR2SPR,             // 160
+	KEENSHINNYR3SPR,             // 161
+	KEENSLIDED1SPR,              // 162
+	KEENSLIDED2SPR,              // 163
+	KEENSLIDED3SPR,              // 164
+	KEENSLIDED4SPR,              // 165
+	KEENSHINNYL1SPR,             // 166
+	KEENSHINNYL2SPR,             // 167
+	KEENSHINNYL3SPR,             // 168
+	KEENPLSHOOTUSPR,             // 169
+	KEENPRSHOOTUSPR,             // 170
+	KEENPRSHOOTDSPR,             // 171
+	KEENPLSHOOTDSPR,             // 172
+	KEENPSHOOTLSPR,              // 173
+	KEENPSHOOTRSPR,              // 174
+	KEENENTER1SPR,               // 175
+	KEENENTER2SPR,               // 176
+	KEENENTER3SPR,               // 177
+	KEENENTER4SPR,               // 178
+	KEENENTER5SPR,               // 179
+	KEENHANGLSPR,                // 180
+	KEENHANGRSPR,                // 181
+	KEENCLIMBEDGEL1SPR,          // 182
+	KEENCLIMBEDGEL2SPR,          // 183
+	KEENCLIMBEDGEL3SPR,          // 184
+	KEENCLIMBEDGEL4SPR,          // 185
+	KEENCLIMBEDGER1SPR,          // 186
+	KEENCLIMBEDGER2SPR,          // 187
+	KEENCLIMBEDGER3SPR,          // 188
+	KEENCLIMBEDGER4SPR,          // 189
+	KEENPOGOR1SPR,               // 190
+	KEENPOGOR2SPR,               // 191
+	KEENPOGOL1SPR,               // 192
+	KEENPOGOL2SPR,               // 193
+	BONUS100UPSPR,               // 194
+	BONUS100SPR,                 // 195
+	BONUS200SPR,                 // 196
+	BONUS500SPR,                 // 197
+	BONUS1000SPR,                // 198
+	BONUS2000SPR,                // 199
+	BONUS5000SPR,                // 200
+	BONUS1UPSPR,                 // 201
+	BONUSCLIPSPR,                // 202
+	VIVAPOOF1SPR,                // 203
+	VIVAPOOF2SPR,                // 204
+	VIVAPOOF3SPR,                // 205
+	VIVAPOOF4SPR,                // 206
+	END_LUMP(KEEN_LUMP_END, __KEENEND)
+
+	START_LUMP(KEYCARD_LUMP_START, __KEYCARDSTART)
+	DOORCARD1SPR,                // 207
+	DOORCARD2SPR,                // 208
+	BONUSCARDSPR,                // 209
+	END_LUMP(KEYCARD_LUMP_END, __KEYCARDEND)
+
+	START_LUMP(SUGAR1_LUMP_START, __SUGAR1START)
+	SUGAR1ASPR,                  // 210
+	SUGAR1BSPR,                  // 211
+	END_LUMP(SUGAR1_LUMP_END, __SUGAR1END)
+
+	START_LUMP(SUGAR2_LUMP_START, __SUGAR2START)
+	SUGAR2ASPR,                  // 212
+	SUGAR2BSPR,                  // 213
+	END_LUMP(SUGAR2_LUMP_END, __SUGAR2END)
+
+	START_LUMP(SUGAR3_LUMP_START, __SUGAR3START)
+	SUGAR3ASPR,                  // 214
+	SUGAR3BSPR,                  // 215
+	END_LUMP(SUGAR3_LUMP_END, __SUGAR3END)
+
+	START_LUMP(SUGAR4_LUMP_START, __SUGAR4START)
+	SUGAR4ASPR,                  // 216
+	SUGAR4BSPR,                  // 217
+	END_LUMP(SUGAR4_LUMP_END, __SUGAR4END)
+
+	START_LUMP(SUGAR5_LUMP_START, __SUGAR5START)
+	SUGAR5ASPR,                  // 218
+	SUGAR5BSPR,                  // 219
+	END_LUMP(SUGAR5_LUMP_END, __SUGAR5END)
+
+	START_LUMP(SUGAR6_LUMP_START, __SUGAR6START)
+	SUGAR6ASPR,                  // 220
+	SUGAR6BSPR,                  // 221
+	END_LUMP(SUGAR6_LUMP_END, __SUGAR6END)
+
+	START_LUMP(ONEUP_LUMP_START, __ONEUPSTART)
+	ONEUPASPR,                   // 222
+	ONEUPBSPR,                   // 223
+	END_LUMP(ONEUP_LUMP_END, __ONEUPEND)
+
+	START_LUMP(KEYGEM_LUMP_START, __KEYGEMSTART)
+	REDGEM1SPR,                  // 224
+	REDGEM2SPR,                  // 225
+	YELLOWGEM1SPR,               // 226
+	YELLOWGEM2SPR,               // 227
+	BLUEGEM1SPR,                 // 228
+	BLUEGEM2SPR,                 // 229
+	GREENGEM1SPR,                // 230
+	GREENGEM2SPR,                // 231
+	BONUSGEMSPR,                 // 232
+	END_LUMP(KEYGEM_LUMP_END, __KEYGEMEND)
+
+	START_LUMP(AMMO_LUMP_START, __AMMOSTART)
+	STUNCLIP1SPR,                // 233
+	STUNCLIP2SPR,                // 234
+	END_LUMP(AMMO_LUMP_END, __AMMOEND)
+
+	SCOREBOXSPR,                 // 235
+
+	START_LUMP(LASER_LUMP_START, __LASERSTART)
+	LASER1SPR,                   // 236
+	LASER2SPR,                   // 237
+	LASER3SPR,                   // 238
+	LASER4SPR,                   // 239
+	LASERHIT1SPR,                // 240
+	LASERHIT2SPR,                // 241
+	END_LUMP(LASER_LUMP_END, __LASEREND)
+
+	START_LUMP(WORLDKEEN_LUMP_START, __WORLDKEENSTART)
+	WORLDKEENL1SPR,              // 242
+	WORLDKEENL2SPR,              // 243
+	WORLDKEENL3SPR,              // 244
+	WORLDKEENR1SPR,              // 245
+	WORLDKEENR2SPR,              // 246
+	WORLDKEENR3SPR,              // 247
+	WORLDKEENU1SPR,              // 248
+	WORLDKEENU2SPR,              // 249
+	WORLDKEENU3SPR,              // 250
+	WORLDKEEND1SPR,              // 251
+	WORLDKEEND2SPR,              // 252
+	WORLDKEEND3SPR,              // 253
+	WORLDKEENDR1SPR,             // 254
+	WORLDKEENDR2SPR,             // 255
+	WORLDKEENDR3SPR,             // 256
+	WORLDKEENDL1SPR,             // 257
+	WORLDKEENDL2SPR,             // 258
+	WORLDKEENDL3SPR,             // 259
+	WORLDKEENUL1SPR,             // 260
+	WORLDKEENUL2SPR,             // 261
+	WORLDKEENUL3SPR,             // 262
+	WORLDKEENUR1SPR,             // 263
+	WORLDKEENUR2SPR,             // 264
+	WORLDKEENUR3SPR,             // 265
+	WORLDKEENWAVE1SPR,           // 266
+	WORLDKEENWAVE2SPR,           // 267
+	FLAGFLIP1SPR,                // 268
+	FLAGFLIP2SPR,                // 269
+	FLAGFLIP3SPR,                // 270
+	FLAGFLIP4SPR,                // 271
+	FLAGFLIP5SPR,                // 272
+	FLAGFALL1SPR,                // 273
+	FLAGFALL2SPR,                // 274
+	FLAGFLAP1SPR,                // 275
+	FLAGFLAP2SPR,                // 276
+	FLAGFLAP3SPR,                // 277
+	FLAGFLAP4SPR,                // 278
+	SHOOTINGSTAR1SPR,            // 279
+	SHOOTINGSTAR2SPR,            // 280
+	WORLDTELSPARK1SPR,           // 281
+	WORLDTELSPARK2SPR,           // 282
+	END_LUMP(WORLDKEEN_LUMP_END, __WORLDKEENEND)
+
+	START_LUMP(FUSE_LUMP_START, __FUSESTART)
+	FUSEFLASH1SPR,               // 283
+	FUSEFLASH2SPR,               // 284
+	FUSEFLASH3SPR,               // 285
+	END_LUMP(FUSE_LUMP_END, __FUSEEND)
+
+	START_LUMP(STAREXPLODE_LUMP_START, __SMALLSPARKSTART)
+	STAREXPLODE1SPR,             // 286
+	STAREXPLODE2SPR,             // 287
+	STAREXPLODE3SPR,             // 288
+	STAREXPLODE4SPR,             // 289
+	END_LUMP(STAREXPLODE_LUMP_END, __SMALLSPARKEND)
+
+	START_LUMP(TELEPORT_LUMP_START, __TELEPORTSTART)
+	TELEPORTSPARK1SPR,           // 290
+	TELEPORTSPARK2SPR,           // 291
+	TELEPORTZAP1SPR,             // 292
+	TELEPORTZAP2SPR,             // 293
+	END_LUMP(TELEPORT_LUMP_END, __TELEPORTEND)
+
+	START_LUMP(SCOTTIE_LUMP_START, __KORATHSTART)
+	SCOTTIEWALKL1SPR,            // 294
+	SCOTTIEWALKL2SPR,            // 295
+	SCOTTIEWALKL3SPR,            // 296
+	SCOTTIEWALKL4SPR,            // 297
+	SCOTTIEWALKR1SPR,            // 298
+	SCOTTIEWALKR2SPR,            // 299
+	SCOTTIEWALKR3SPR,            // 300
+	SCOTTIEWALKR4SPR,            // 301
+	SCOTTIEFACESPR,              // 302
+	SCOTTIESTUNSPR,              // 303
+	END_LUMP(SCOTTIE_LUMP_END, __KORATHEND)
+
+	START_LUMP(MASTER_LUMP_START, __MASTERSTART)
+	MASTER1SPR,                  // 304
+	MASTER2SPR,                  // 305
+	MASTER3SPR,                  // 306
+	MASTER4SPR,                  // 307
+	MASTERTELEPORT1SPR,          // 308
+	MASTERTELEPORT2SPR,          // 309
+	SHIKMASTERCASTRSPR,          // 310
+	SHIKMASTERCASTLSPR,          // 311
+	MASTERFLOORSPARK1SPR,        // 312
+	MASTERFLOORSPARK2SPR,        // 313
+	MASTERFLOORSPARK3SPR,        // 314
+	MASTERFLOORSPARK4SPR,        // 315
+	MASTERSHOT1SPR,              // 316
+	MASTERSHOT2SPR,              // 317
+	MASTERSHOT3SPR,              // 318
+	MASTERSHOT4SPR,              // 319
+	END_LUMP(MASTER_LUMP_END, __MASTEREND)
+
+	START_LUMP(SHIKADI_LUMP_START, __SHIKADISTART)
+	SHIKADI1SPR,                 // 320
+	SHIKADI2SPR,                 // 321
+	SHIKADI3SPR,                 // 322
+	SHIKADI4SPR,                 // 323
+	SHIKADIGRABRSPR,             // 324
+	SHIKADIGRABLSPR,             // 325
+	SHIKADIPOLESPARK1SPR,        // 326
+	SHIKADIPOLESPARK2SPR,        // 327
+	SHIKADIWALKR1SPR,            // 328
+	SHIKADIWALKR2SPR,            // 329
+	SHIKADIWALKR3SPR,            // 330
+	SHIKADIWALKR4SPR,            // 331
+	SHIKADIWALKL1SPR,            // 332
+	SHIKADIWALKL2SPR,            // 333
+	SHIKADIWALKL3SPR,            // 334
+	SHIKADIWALKL4SPR,            // 335
+	SHIKADISTUNSPR,              // 336
+	END_LUMP(SHIKADI_LUMP_END, __SHIKADIEND)
+
+	START_LUMP(SHOCKSHUND_LUMP_START, __SHOCKSHUNDSTART)
+	PETSIT1SPR,                  // 337
+	PETSIT2SPR,                  // 338
+	PETRUNR1SPR,                 // 339
+	PETRUNR2SPR,                 // 340
+	PETRUNR3SPR,                 // 341
+	PETRUNR4SPR,                 // 342
+	PETRUNL1SPR,                 // 343
+	PETRUNL2SPR,                 // 344
+	PETRUNL3SPR,                 // 345
+	PETRUNL4SPR,                 // 346
+	PETJUMPLSPR,                 // 347
+	PETJUMPRSPR,                 // 348
+	PETBARKR1SPR,                // 349
+	PETBARKR2SPR,                // 350
+	PETBARKL1SPR,                // 351
+	PETBARKL2SPR,                // 352
+	PETSTUNSPR,                  // 353
+	PETSPARK1SPR,                // 354
+	PETSPARK2SPR,                // 355
+	PETSPARKHIT1SPR,             // 356
+	PETSPARKHIT2SPR,             // 357
+	END_LUMP(SHOCKSHUND_LUMP_END, __SHOCKSHUNDEND)
+
+	START_LUMP(SPHEREFUL_LUMP_START, __SPHEREFULSTART)
+	SPHEREFUL1SPR,               // 358
+	SPHEREFUL2SPR,               // 359
+	SPHEREFUL3SPR,               // 360
+	SPHEREFUL4SPR,               // 361
+	SPHEREGUARD1SPR,             // 362
+	SPHEREGUARD2SPR,             // 363
+	SPHEREGUARD3SPR,             // 364
+	SPHEREGUARD4SPR,             // 365
+	END_LUMP(SPHEREFUL_LUMP_END, __SPHEREFULEND)
+
+	START_LUMP(SPARKY_LUMP_START, __SPARKYSTART)
+	SPARKYWALKL1SPR,             // 366
+	SPARKYWALKL2SPR,             // 367
+	SPARKYWALKL3SPR,             // 368
+	SPARKYWALKL4SPR,             // 369
+	SPARKYTURN1SPR,              // 370
+	SPARKYTURN2SPR,              // 371
+	SPARKYTURN3SPR,              // 372
+	SPARKYWALKR1SPR,             // 373
+	SPARKYWALKR2SPR,             // 374
+	SPARKYWALKR3SPR,             // 375
+	SPARKYWALKR4SPR,             // 376
+	SPARKYSTUNSPR,               // 377
+	END_LUMP(SPARKY_LUMP_END, __SPARKYEND)
+
+	START_LUMP(MINE_LUMP_START, __MINESTART)
+	SHIKADIMINESPR,              // 378
+	SHIKADIMINEEYESPR,           // 379
+	SHIKADIMINEPULSE1SPR,        // 380
+	SHIKADIMINEPULSE2SPR,        // 381
+	SHIKADIMINEBOOM1SPR,         // 382
+	SHIKADIMINEBOOM2SPR,         // 383
+	SHIKADIMINEPIECESPR,         // 384
+	END_LUMP(MINE_LUMP_END, __MINEEND)
+
+	START_LUMP(SLICESTAR_LUMP_START, __SLICESTARSTART)
+	SLICESTARSPR,                // 385
+	SLICESTARBOOMSPR,            // 386
+	END_LUMP(SLICESTAR_LUMP_END, __SLICASTAREND)
+
+	START_LUMP(ROBORED_LUMP_START, __ROBOREDSTART)
+	ROBOREDRSPR,                 // 387
+	ROBOREDLSPR,                 // 388
+	ROBOSHOT1SPR,                // 389
+	ROBOSHOT2SPR,                // 390
+	ROBOSHOTHIT1SPR,             // 391
+	ROBOSHOTHIT2SPR,             // 392
+	END_LUMP(ROBORED_LUMP_END, __ROBOREDEND)
+
+	START_LUMP(SPIRO_LUMP_START, __SPIROSTART)
+	SPIROSITDSPR,                // 393
+	SPIROSITLSPR,                // 394
+	SPIROSITUSPR,                // 395
+	SPIROSITRSPR,                // 396
+	SPIROSPINULSPR,              // 397
+	SPIROSPINURSPR,              // 398
+	SPIROSPINDRSPR,              // 399
+	SPIROSPINDLSPR,              // 400
+	SPIROSPINDSPR,               // 401
+	SPIROSPINLSPR,               // 402
+	SPIROSPINUSPR,               // 403
+	SPIROSPINRSPR,               // 404
+	END_LUMP(SPIRO_LUMP_END, __SPIROEND)
+
+	START_LUMP(AMPTON_LUMP_START, __AMPTONSTART)
+	AMPTONWALKR1SPR,             // 405
+	AMPTONWALKR2SPR,             // 406
+	AMPTONWALKR3SPR,             // 407
+	AMPTONWALKR4SPR,             // 408
+	AMPTONFACESPR,               // 409
+	AMPTONGRAB1SPR,              // 410
+	AMPTONGRAB2SPR,              // 411
+	AMTONWALKL1SPR,              // 412
+	AMTONWALKL2SPR,              // 413
+	AMTONWALKL3SPR,              // 414
+	AMTONWALKL4SPR,              // 415
+	AMPTONSTUNSPR,               // 416
+	END_LUMP(AMPTON_LUMP_END, __AMPTONEND)
+
+	START_LUMP(VOLTE_LUMP_START, __VOLTESTART)
+	VOLTEFACE1SPR,               // 417
+	VOLTEFACE2SPR,               // 418
+	VOLTEFACE3SPR,               // 419
+	VOLTEFACE4SPR,               // 420
+	VOLTEFACESTUNSPR,            // 421
+	END_LUMP(VOLTE_LUMP_END, __VOLTEEND)
+
+	START_LUMP(SLOTPLAT_LUMP_START, __PINKPLATSTART)
+	SLOTPLAT1SPR,                // 422
+	SLOTPLAT2SPR,                // 423
+	END_LUMP(SLOTPLAT_LUMP_END, __PINKPLATEND)
+
+	START_LUMP(SPINDRED_LUMP_START, __SPINDREDSTART)
+	SPINDRED1SPR,                // 424
+	SPINDRED2SPR,                // 425
+	SPINDRED3SPR,                // 426
+	SPINDRED4SPR,                // 427
+	END_LUMP(SPINDRED_LUMP_END, __SPINDREDEND)
+
+	START_LUMP(SHELLEY_LUMP_START, __SHELLEYSTART)
+	SHELLEYR1SPR,                // 428
+	SHELLEYR2SPR,                // 429
+	SHELLEYR3SPR,                // 430
+	SHELLEYR4SPR,                // 431
+	SHELLEYL1SPR,                // 432
+	SHELLEYL2SPR,                // 433
+	SHELLEYL3SPR,                // 434
+	SHELLEYL4SPR,                // 435
+	SHELLEYJUMPRSPR,             // 436
+	SHELLEYFALLRSPR,             // 437
+	SHELLEYJUMPLSPR,             // 438
+	SHELLEYFALLLSPR,             // 439
+	SHELLEYBOOM1SPR,             // 440
+	SHELLEYBOOM2SPR,             // 441
+	SHELLEYBOOM3SPR,             // 442
+	SHELLEYBOOM4SPR,             // 443
+	SHELLEYPIECE1SPR,            // 444
+	SHELLEYPIECE2SPR,            // 445
+	END_LUMP(SHELLEY_LUMP_END, __SHELLEYEND)
+
+	START_LUMP(PLATFORM_LUMP_START, __PLATFORMSTART)
+	PLATFORMSPR,                 // 446
+	END_LUMP(PLATFORM_LUMP_END, __PLATFORMEND)
+
+	START_LUMP(MINIPLAT_LUMP_START, __MINIPLATSTART)
+	MINIPLATSPR,                // 447
+	END_LUMP(MINIPLAT_LUMP_END, __MINIPLATEND)
+
+
+	//
+	// TILES (these don't need names)
+	//
+
+	LASTTILE=STARTEXTERNS-1,
+
+	//
+	// EXTERNS
+	//
+
+	//texts
+	T_HELPART,                   // 4914
+	T_CONTRART,                  // 4915
+	T_STORYART,                  // 4916
+	T_IDART,                     // 4917
+	T_ENDART,                    // 4918
+	T_ENDART2,                   // 4919
+	T_ORDERART,                  // 4920
+
+	ORDERSCREEN,                 // 4921
+	OUTOFMEM,                    // 4922
+	GALAXY,                      // 4923
+
+	//demos
+	DEMO0,                       // 4924
+	DEMO1,                       // 4925
+	DEMO2,                       // 4926
+	DEMO3,                       // 4927
+	DEMO4,                       // 4928
+
+	NUMGRCHUNKS
+} graphicnums;
+
+#undef START_LUMP
+#undef END_LUMP
+
+#endif //__GFX_H__
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/KEEN5C/ID_ASM.EQU b/16/keen456/KEEN4-6/KEEN5C/ID_ASM.EQU
new file mode 100755
index 00000000..b45d7cac
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN5C/ID_ASM.EQU
@@ -0,0 +1,115 @@
+;
+; Equates for all .ASM files
+;
+
+;----------------------------------------------------------------------------
+
+INCLUDE	"GFXC_CK5.EQU"
+
+;----------------------------------------------------------------------------
+
+CGAGR		=	1
+EGAGR		=	2
+VGAGR		=	3
+
+GRMODE		=	CGAGR
+PROFILE		=	0			; 1=keep stats on tile drawing
+
+SC_INDEX	=	03C4h
+SC_RESET	=	0
+SC_CLOCK	=	1
+SC_MAPMASK	=	2
+SC_CHARMAP	=	3
+SC_MEMMODE	=	4
+
+CRTC_INDEX	=	03D4h
+CRTC_H_TOTAL	=	0
+CRTC_H_DISPEND	=	1
+CRTC_H_BLANK	=	2
+CRTC_H_ENDBLANK	=	3
+CRTC_H_RETRACE	=	4
+CRTC_H_ENDRETRACE =	5
+CRTC_V_TOTAL	=	6
+CRTC_OVERFLOW	=	7
+CRTC_ROWSCAN	=	8
+CRTC_MAXSCANLINE =	9
+CRTC_CURSORSTART =	10
+CRTC_CURSOREND	=	11
+CRTC_STARTHIGH	=	12
+CRTC_STARTLOW	=	13
+CRTC_CURSORHIGH	=	14
+CRTC_CURSORLOW	=	15
+CRTC_V_RETRACE	=	16
+CRTC_V_ENDRETRACE =	17
+CRTC_V_DISPEND	=	18
+CRTC_OFFSET	=	19
+CRTC_UNDERLINE	=	20
+CRTC_V_BLANK	=	21
+CRTC_V_ENDBLANK	=	22
+CRTC_MODE	=	23
+CRTC_LINECOMPARE =	24
+
+
+GC_INDEX	=	03CEh
+GC_SETRESET	=	0
+GC_ENABLESETRESET =	1
+GC_COLORCOMPARE	=	2
+GC_DATAROTATE	=	3
+GC_READMAP	=	4
+GC_MODE		=	5
+GC_MISCELLANEOUS =	6
+GC_COLORDONTCARE =	7
+GC_BITMASK	=	8
+
+ATR_INDEX	=	03c0h
+ATR_MODE	=	16
+ATR_OVERSCAN	=	17
+ATR_COLORPLANEENABLE =	18
+ATR_PELPAN	=	19
+ATR_COLORSELECT	=	20
+
+STATUS_REGISTER_1     =	03dah
+
+
+MACRO	WORDOUT
+	out	dx,ax
+ENDM
+
+if 0
+
+MACRO	WORDOUT
+	out	dx,al
+	inc	dx
+	xchg	al,ah
+	out	dx,al
+	dec	dx
+	xchg	al,ah
+ENDM
+
+endif
+
+UPDATEWIDE	=	22
+UPDATEHIGH	=	14
+
+;
+; tile info offsets from segment tinf
+;
+
+ANIM		=	402
+SPEED		=	(ANIM+NUMTILE16)
+
+NORTHWALL	=	(SPEED+NUMTILE16)
+EASTWALL	=	(NORTHWALL+NUMTILE16M)
+SOUTHWALL   =	(EASTWALL+NUMTILE16M)
+WESTWALL    =	(SOUTHWALL+NUMTILE16M)
+MANIM       =	(WESTWALL+NUMTILE16M)
+INTILE      =	(MANIM+NUMTILE16M)
+MSPEED      =	(INTILE+NUMTILE16M)
+
+
+IFE GRMODE-EGAGR
+SCREENWIDTH	=	64
+ENDIF
+IFE GRMODE-CGAGR
+SCREENWIDTH	=	128
+ENDIF
diff --git a/16/keen456/KEEN4-6/KEEN5C/ID_HEADS.H b/16/keen456/KEEN4-6/KEEN5C/ID_HEADS.H
new file mode 100755
index 00000000..210a4110
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN5C/ID_HEADS.H
@@ -0,0 +1,109 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+// ID_GLOB.H
+
+
+#include <ALLOC.H>
+#include <CTYPE.H>
+#include <DOS.H>
+#include <ERRNO.H>
+#include <FCNTL.H>
+#include <IO.H>
+#include <MEM.H>
+#include <PROCESS.H>
+#include <STDIO.H>
+#include <STDLIB.H>
+#include <STRING.H>
+#include <SYS\STAT.H>
+
+#define __ID_GLOB__
+
+//--------------------------------------------------------------------------
+
+#define KEEN
+#define KEEN5
+
+#define	EXTENSION	"CK5"
+
+extern	char far introscn;
+
+#include "GFXC_CK5.H"
+#include "AUDIOCK5.H"
+
+//--------------------------------------------------------------------------
+
+#define	TEXTGR	0
+#define	CGAGR	1
+#define	EGAGR	2
+#define	VGAGR	3
+
+#define GRMODE	CGAGR
+
+#if GRMODE == EGAGR
+#define GREXT	"EGA"
+#endif
+#if GRMODE == CGAGR
+#define GREXT	"CGA"
+#endif
+
+//#define PROFILE
+
+//
+//	ID Engine
+//	Types.h - Generic types, #defines, etc.
+//	v1.0d1
+//
+
+#ifndef	__TYPES__
+#define	__TYPES__
+
+typedef	enum	{false,true}	boolean;
+typedef	unsigned	char		byte;
+typedef	unsigned	int			word;
+typedef	unsigned	long		longword;
+typedef	byte *					Ptr;
+
+typedef	struct
+		{
+			int	x,y;
+		} Point;
+typedef	struct
+		{
+			Point	ul,lr;
+		} Rect;
+
+#define	nil	((void *)0)
+
+#endif
+
+#include "ID_MM.H"
+#include "ID_CA.H"
+#include "ID_VW.H"
+#include "ID_RF.H"
+#include "ID_IN.H"
+#include "ID_SD.H"
+#include "ID_US.H"
+
+
+void	Quit (char *error);		// defined in user program
+
diff --git a/16/keen456/KEEN4-6/KEEN6/AUDIOCK6.H b/16/keen456/KEEN4-6/KEEN6/AUDIOCK6.H
new file mode 100755
index 00000000..d3407ceb
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN6/AUDIOCK6.H
@@ -0,0 +1,136 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+#ifndef __AUDIO_H__
+#define __AUDIO_H__
+
+//#include "VERSION.H"
+
+/////////////////////////////////////////////////
+//
+// MUSE Header for .CK6
+//
+/////////////////////////////////////////////////
+
+#define NUMSOUNDS     LASTSOUND
+#define NUMSNDCHUNKS  ((3*LASTSOUND)+LASTMUSIC)
+
+//
+// Sound names & indexes
+//
+typedef enum {
+	SND_WORLDWALK1,        // 0
+	SND_WORLDWALK2,        // 1
+	SND_JUMP,              // 2
+	SND_LAND,              // 3
+	SND_KEENFIRE,          // 4
+	SND_DROPKEY,           // 5
+	SND_BLORBBOUNCE,       // 6
+	SND_POGOBOUNCE,        // 7
+	SND_GETPOINTS,         // 8
+	SND_GETAMMO,           // 9
+	SND_GETWATER,          // 10
+	SND_11,                // 11
+	SND_ENTERLEVEL,        // 12
+	SND_LEVELDONE,         // 13
+	SND_NOWAY,             // 14
+	SND_HELMETHIT,         // 15
+	SND_16,                // 16
+	SND_EXTRAKEEN,         // 17
+	SND_OPENDOOR,          // 18
+	SND_GETKEY,            // 19
+	SND_PLUMMET,           // 20
+	SND_USESWITCH,         // 21
+	SND_BIPSQUISH,         // 22
+	SND_KEENDEAD,          // 23
+	SND_BIPSHIPEXPLODE,    // 24
+	SND_SHOTEXPLODE,       // 25
+	SND_BOBBAJUMP,         // 26
+	SND_BOBBALAND,         // 27
+	SND_28,                // 28
+	SND_ENEMYSHOT,         // 29
+	SND_ENEMYSHOTEXPLODE,  // 30
+	SND_BOBBASHOT,         // 31
+	SND_32,                // 32
+	SND_GRABSATELLITE,     // 33
+	SND_SHOWSTATUS,        // 34
+	SND_HIDESTATUS,        // 35
+	SND_GIKJUMP,           // 36
+	SND_GIKLAND,           // 37
+	SND_ORBATRIXBOUNCE,    // 38
+	SND_39,                // 39
+	SND_40,                // 40
+	SND_TELEPORT,          // 41
+	SND_SHOTBOUNCE,        // 42
+	SND_FLAGSPIN,          // 43
+	SND_FLAGLAND,          // 44
+	SND_QUESTITEM,         // 45
+	KEENPADDLESND,         // 46
+	BALLBOUNCESND,         // 47
+	COMPPADDLESND,         // 48
+	COMPSCOREDSND,         // 49
+	KEENSCOREDSND,         // 50
+	SND_CEILICKATTACK,     // 51
+	SND_SMASH,             // 52
+	SND_THROWROPE,         // 53
+	SND_ROCKETFLY,         // 54
+	SND_CEILICKLAUGH,      // 55
+	SND_ROCKETSTART,       // 56
+	SND_GRABBITER,         // 57
+	SND_STOMP,             // 58
+	SND_FLAME,             // 59
+	LASTSOUND
+} soundnames;
+
+#if LASTSOUND != 60
+#error bad sound enum!
+#endif
+
+#define NOWAYSND SND_NOWAY
+
+//
+// Base offsets
+//
+#define STARTPCSOUNDS     0
+#define STARTADLIBSOUNDS  (STARTPCSOUNDS+NUMSOUNDS)
+#define STARTDIGISOUNDS   (STARTADLIBSOUNDS+NUMSOUNDS)
+#define STARTMUSIC        (STARTDIGISOUNDS+NUMSOUNDS)
+
+//
+// Music names & indexes
+//
+typedef enum {
+	WONDER_MUS,
+	BRERTAR_MUS,
+	TOFUTURE_MUS,
+	FASTER_MUS,
+	SPACFUNK_MUS,
+	ALIENATE_MUS,
+	OMINOUS_MUS,
+	METAL_MUS,
+	MAMSNAKE_MUS,
+	LASTMUSIC
+} musicnames;
+
+/////////////////////////////////////////////////
+//
+// Thanks for playing with MUSE!
+//
+/////////////////////////////////////////////////
+
+#endif
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/KEEN6/GFXE_CK6.EQU b/16/keen456/KEEN4-6/KEEN6/GFXE_CK6.EQU
new file mode 100755
index 00000000..d3b3d6dc
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN6/GFXE_CK6.EQU
@@ -0,0 +1,55 @@
+;=====================================
+;
+; Graphics .EQU file for .CK6
+; not IGRAB-ed :)
+;
+;=====================================
+
+;INCLUDE "VERSION.EQU"
+
+;
+; Amount of each data item
+;
+NUMFONT     =	3
+NUMFONTM    =	0
+NUMPICM     =	3
+NUMTILE8    =	108
+NUMTILE8M   =	36
+NUMTILE32   =	0
+NUMTILE32M  =	0
+
+;
+; Amount of each item in episode 6
+;
+NUMPICS     =	37
+NUMSPRITES  =	390
+NUMTILE16   =	2376
+NUMTILE16M  =	2736
+NUMEXTERN   =	11
+
+
+;
+; File offsets for data items
+;
+STRUCTPIC       =	0
+STRUCTPICM      =	1
+STRUCTSPRITE    =	2
+
+STARTFONT       =	3
+STARTFONTM      =	(STARTFONT+NUMFONT)
+STARTPICS       =	(STARTFONTM+NUMFONTM)
+STARTPICM       =	(STARTPICS+NUMPICS)
+STARTSPRITES    =	(STARTPICM+NUMPICM)
+STARTTILE8      =	(STARTSPRITES+NUMSPRITES)
+STARTTILE8M     =	(STARTTILE8+1)
+STARTTILE16     =	(STARTTILE8M+1)
+STARTTILE16M    =	(STARTTILE16+NUMTILE16)
+STARTTILE32     =	(STARTTILE16M+NUMTILE16M)
+STARTTILE32M    =	(STARTTILE32+NUMTILE32)
+STARTEXTERN     =	(STARTTILE32M+NUMTILE32M)
+
+NUMCHUNKS       =	(STARTEXTERN+NUMEXTERN)
+
+;
+; Thank you for using IGRAB!
+;
diff --git a/16/keen456/KEEN4-6/KEEN6/GFXE_CK6.H b/16/keen456/KEEN4-6/KEEN6/GFXE_CK6.H
new file mode 100755
index 00000000..344690a3
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN6/GFXE_CK6.H
@@ -0,0 +1,670 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+#ifndef __GFX_H__
+#define __GFX_H__
+
+//#include "VERSION.H"
+
+//////////////////////////////////////
+//
+// Graphics .H file for .CK6
+// not IGRAB-ed :)
+//
+//////////////////////////////////////
+
+//
+// Lump creation macros
+//
+
+#define START_LUMP(actualname, dummyname) actualname, dummyname=actualname-1,
+#define END_LUMP(actualname, dummyname) dummyname, actualname=dummyname-1,
+
+//
+// Amount of each data item
+//
+
+//common numbers:
+#define NUMCHUNKS    NUMGRCHUNKS
+#define NUMFONT      3
+#define NUMFONTM     0
+#define NUMPICM      3
+#define NUMTILE8     108	// BUG: only 104 tiles exist in EGAGRAPH!
+#define NUMTILE8M    36		// BUG: only 12 tiles exist in EGAGRAPH!
+#define NUMTILE32    0
+#define NUMTILE32M   0
+
+//episode-specific numbers:
+#define NUMPICS      37
+#define NUMSPRITES   390
+#define NUMTILE16    2376
+#define NUMTILE16M   2736
+#define NUMEXTERNS   10
+
+//
+// File offsets for data items
+//
+#define STRUCTPIC    0
+#define STRUCTPICM   1
+#define STRUCTSPRITE 2
+
+#define STARTFONT    3
+#define STARTFONTM   (STARTFONT+NUMFONT)
+#define STARTPICS    (STARTFONTM+NUMFONTM)
+#define STARTPICM    (STARTPICS+NUMPICS)
+#define STARTSPRITES (STARTPICM+NUMPICM)
+#define STARTTILE8   (STARTSPRITES+NUMSPRITES)
+#define STARTTILE8M  (STARTTILE8+1)
+#define STARTTILE16  (STARTTILE8M+1)
+#define STARTTILE16M (STARTTILE16+NUMTILE16)
+#define STARTTILE32  (STARTTILE16M+NUMTILE16M)
+#define STARTTILE32M (STARTTILE32+NUMTILE32)
+#define STARTEXTERNS (STARTTILE32M+NUMTILE32M)
+
+typedef enum {
+	LASTFONT=STARTPICS-1,
+
+	//
+	// PICS
+	//
+
+	H_END1PIC,                   // 6
+	H_END2PIC,                   // 7
+	H_END3PIC,                   // 8
+	H_END4PIC,                   // 9
+	H_END5PIC,                   // 10
+
+	START_LUMP(CONTROLS_LUMP_START, __CONTROLSSTART)
+	CP_MAINMENUPIC,              // 11
+	CP_NEWGAMEMENUPIC,           // 12
+	CP_LOADMENUPIC,              // 13
+	CP_SAVEMENUPIC,              // 14
+	CP_CONFIGMENUPIC,            // 15
+	CP_SOUNDMENUPIC,             // 16
+	CP_MUSICMENUPIC,             // 17
+	CP_KEYBOARDMENUPIC,          // 18
+	CP_KEYMOVEMENTPIC,           // 19
+	CP_KEYBUTTONPIC,             // 20
+	CP_JOYSTICKMENUPIC,          // 21
+	CP_OPTIONSMENUPIC,           // 22
+	CP_PADDLEWARPIC,             // 23
+	CP_QUITPIC,                  // 24
+	CP_JOYSTICKPIC,              // 25
+	CP_MENUSCREENPIC,            // 26
+	END_LUMP(CONTROLS_LUMP_END, __CONTROLSEND)
+
+	H_FLASHARROW1PIC,            // 27
+	H_FLASHARROW2PIC,            // 28
+	IDSOFTPIC,                   // 29
+	PROGTEAMPIC,                 // 30
+	ARTISTPIC,                   // 31
+	DIRECTORPIC,                 // 32
+	SW_BACKGROUNDPIC,            // 33
+	TITLEPICPIC,                 // 34
+	KEENTALK1PIC,                // 35
+	KEENTALK2PIC,                // 36
+	KEENCOUNT1PIC,               // 37
+	KEENCOUNT2PIC,               // 38
+	KEENCOUNT3PIC,               // 39
+	KEENCOUNT4PIC,               // 40
+	KEENCOUNT5PIC,               // 41
+	KEENCOUNT6PIC,               // 42
+
+	//
+	// MASKED PICS
+	//
+
+	CP_MENUMASKPICM,             // 43
+	CORDPICM,                    // 44
+	METALPOLEPICM,               // 45
+
+	//
+	// SPRITES
+	//
+
+	START_LUMP(PADDLE_LUMP_START, __PADDLESTART)
+	PADDLESPR,                   // 46
+	BALLSPR,                     // 47
+	BALL1PIXELTOTHERIGHTSPR,     // 48
+	BALL2PIXELSTOTHERIGHTSPR,    // 49
+	BALL3PIXELSTOTHERIGHTSPR,    // 50
+	END_LUMP(PADDLE_LUMP_END, __PADDLEEND)
+
+	DEMOPLAQUESPR,               // 51
+
+	START_LUMP(KEEN_LUMP_START, __KEENSTART)
+	KEENSTANDRSPR,               // 52
+	KEENRUNR1SPR,                // 53
+	KEENRUNR2SPR,                // 54
+	KEENRUNR3SPR,                // 55
+	KEENRUNR4SPR,                // 56
+	KEENJUMPR1SPR,               // 57
+	KEENJUMPR2SPR,               // 58
+	KEENJUMPR3SPR,               // 59
+	KEENSTANDLSPR,               // 60
+	KEENRUNL1SPR,                // 61
+	KEENRUNL2SPR,                // 62
+	KEENRUNL3SPR,                // 63
+	KEENRUNL4SPR,                // 64
+	KEENJUMPL1SPR,               // 65
+	KEENJUMPL2SPR,               // 66
+	KEENJUMPL3SPR,               // 67
+	KEENLOOKUSPR,                // 68
+	KEENWAITR1SPR,               // 69
+	KEENWAITR2SPR,               // 70
+	KEENWAITR3SPR,               // 71
+	KEENSITREAD1SPR,             // 72
+	KEENSITREAD2SPR,             // 73
+	KEENSITREAD3SPR,             // 74
+	KEENSITREAD4SPR,             // 75
+	KEENREAD1SPR,                // 76
+	KEENREAD2SPR,                // 77
+	KEENREAD3SPR,                // 78
+	KEENSTOPREAD1SPR,            // 79
+	KEENSTOPREAD2SPR,            // 80
+	KEENLOOKD1SPR,               // 81
+	KEENLOOKD2SPR,               // 82
+	KEENDIE1SPR,                 // 83
+	KEENDIE2SPR,                 // 84
+	KEENSTUNSPR,                 // 85
+	STUNSTARS1SPR,               // 86
+	STUNSTARS2SPR,               // 87
+	STUNSTARS3SPR,               // 88
+	KEENSHOOTLSPR,               // 89
+	KEENJLSHOOTLSPR,             // 90
+	KEENJSHOOTDSPR,              // 91
+	KEENJSHOOTUSPR,              // 92
+	KEENSHOOTUSPR,               // 93
+	KEENSHOOTRSPR,               // 94
+	KEENJRSHOOTRSPR,             // 95
+	STUN1SPR,                    // 96
+	STUN2SPR,                    // 97
+	STUN3SPR,                    // 98
+	STUN4SPR,                    // 99
+	STUNHIT1SPR,                 // 100
+	STUNHIT2SPR,                 // 101
+	KEENSHINNYR1SPR,             // 102
+	KEENSHINNYR2SPR,             // 103
+	KEENSHINNYR3SPR,             // 104
+	KEENSLIDED1SPR,              // 105
+	KEENSLIDED2SPR,              // 106
+	KEENSLIDED3SPR,              // 107
+	KEENSLIDED4SPR,              // 108
+	KEENSHINNYL1SPR,             // 109
+	KEENSHINNYL2SPR,             // 110
+	KEENSHINNYL3SPR,             // 111
+	KEENPLSHOOTUSPR,             // 112
+	KEENPRSHOOTUSPR,             // 113
+	KEENPRSHOOTDSPR,             // 114
+	KEENPLSHOOTDSPR,             // 115
+	KEENPSHOOTLSPR,              // 116
+	KEENPSHOOTRSPR,              // 117
+	KEENENTER1SPR,               // 118
+	KEENENTER2SPR,               // 119
+	KEENENTER3SPR,               // 120
+	KEENENTER4SPR,               // 121
+	KEENENTER5SPR,               // 122
+	KEENHANGLSPR,                // 123
+	KEENHANGRSPR,                // 124
+	KEENCLIMBEDGEL1SPR,          // 125
+	KEENCLIMBEDGEL2SPR,          // 126
+	KEENCLIMBEDGEL3SPR,          // 127
+	KEENCLIMBEDGEL4SPR,          // 128
+	KEENCLIMBEDGER1SPR,          // 129
+	KEENCLIMBEDGER2SPR,          // 130
+	KEENCLIMBEDGER3SPR,          // 131
+	KEENCLIMBEDGER4SPR,          // 132
+	KEENPOGOR1SPR,               // 133
+	KEENPOGOR2SPR,               // 134
+	KEENPOGOL1SPR,               // 135
+	KEENPOGOL2SPR,               // 136
+	BONUS100UPSPR,               // 137
+	BONUS100SPR,                 // 138
+	BONUS200SPR,                 // 139
+	BONUS500SPR,                 // 140
+	BONUS1000SPR,                // 141
+	BONUS2000SPR,                // 142
+	BONUS5000SPR,                // 143
+	BONUS1UPSPR,                 // 144
+	BONUSCLIPSPR,                // 145
+	VIVASPLASH1SPR,              // 146
+	VIVASPLASH2SPR,              // 147
+	VIVASPLASH3SPR,              // 148
+	VIVASPLASH4SPR,              // 149
+	END_LUMP(KEEN_LUMP_END, __KEENEND)
+
+	START_LUMP(SUGAR1_LUMP_START, __SUGAR1START)
+	SUGAR1ASPR,                  // 150
+	SUGAR1BSPR,                  // 151
+	END_LUMP(SUGAR1_LUMP_END, __SUGAR1END)
+
+	START_LUMP(SUGAR2_LUMP_START, __SUGAR2START)
+	SUGAR2ASPR,                  // 152
+	SUGAR2BSPR,                  // 153
+	END_LUMP(SUGAR2_LUMP_END, __SUGAR2END)
+
+	START_LUMP(SUGAR3_LUMP_START, __SUGAR3START)
+	SUGAR3ASPR,                  // 154
+	SUGAR3BSPR,                  // 155
+	END_LUMP(SUGAR3_LUMP_END, __SUGAR3END)
+
+	START_LUMP(SUGAR4_LUMP_START, __SUGAR4START)
+	SUGAR4ASPR,                  // 156
+	SUGAR4BSPR,                  // 157
+	END_LUMP(SUGAR4_LUMP_END, __SUGAR4END)
+
+	START_LUMP(SUGAR5_LUMP_START, __SUGAR5START)
+	SUGAR5ASPR,                  // 158
+	SUGAR5BSPR,                  // 159
+	END_LUMP(SUGAR5_LUMP_END, __SUGAR5END)
+
+	START_LUMP(SUGAR6_LUMP_START, __SUGAR6START)
+	SUGAR6ASPR,                  // 160
+	SUGAR6BSPR,                  // 161
+	END_LUMP(SUGAR6_LUMP_END, __SUGAR6END)
+
+	START_LUMP(ONEUP_LUMP_START, __ONEUPSTART)
+	ONEUPASPR,                   // 162
+	ONEUPBSPR,                   // 163
+	END_LUMP(ONEUP_LUMP_END, __ONEUPEND)
+
+	START_LUMP(KEYGEM_LUMP_START, __KEYGEMSTART)
+	REDGEM1SPR,                  // 164
+	REDGEM2SPR,                  // 165
+	YELLOWGEM1SPR,               // 166
+	YELLOWGEM2SPR,               // 167
+	BLUEGEM1SPR,                 // 168
+	BLUEGEM2SPR,                 // 169
+	GREENGEM1SPR,                // 170
+	GREENGEM2SPR,                // 171
+	BONUSGEMSPR,                 // 172
+	END_LUMP(KEYGEM_LUMP_END, __KEYGEMEND)
+
+	START_LUMP(AMMO_LUMP_START, __AMMOSTART)
+	STUNCLIP1SPR,                // 173
+	STUNCLIP2SPR,                // 174
+	END_LUMP(AMMO_LUMP_END, __AMMOEND)
+
+	SCOREBOXSPR,                 // 175
+
+	START_LUMP(LASER_LUMP_START, __LASERSTART)
+	LASER1SPR,                   // 176
+	LASER2SPR,                   // 177
+	LASER3SPR,                   // 178
+	LASER4SPR,                   // 179
+	LASERHIT1SPR,                // 180
+	LASERHIT2SPR,                // 181
+	END_LUMP(LASER_LUMP_END, __LASEREND)
+
+	START_LUMP(SANDWICH_LUMP_START, __SANDWICHSTART)
+	SANDWICHSPR,                 // 182
+	END_LUMP(SANDWICH_LUMP_END, __SANDWICHEND)
+
+	START_LUMP(HOOK_LUMP_START, __ROPESTART)
+	HOOKSPR,                     // 183
+	END_LUMP(HOOK_LUMP_END, __ROPEEND)
+
+	START_LUMP(WORLDKEEN_LUMP_START, __WORLDKEENSTART)
+	WORLDKEENL1SPR,              // 184
+	WORLDKEENL2SPR,              // 185
+	WORLDKEENL3SPR,              // 186
+	WORLDKEENR1SPR,              // 187
+	WORLDKEENR2SPR,              // 188
+	WORLDKEENR3SPR,              // 189
+	WORLDKEENU1SPR,              // 190
+	WORLDKEENU2SPR,              // 191
+	WORLDKEENU3SPR,              // 192
+	WORLDKEEND1SPR,              // 193
+	WORLDKEEND2SPR,              // 194
+	WORLDKEEND3SPR,              // 195
+	WORLDKEENDR1SPR,             // 196
+	WORLDKEENDR2SPR,             // 197
+	WORLDKEENDR3SPR,             // 198
+	WORLDKEENDL1SPR,             // 199
+	WORLDKEENDL2SPR,             // 200
+	WORLDKEENDL3SPR,             // 201
+	WORLDKEENUL1SPR,             // 202
+	WORLDKEENUL2SPR,             // 203
+	WORLDKEENUL3SPR,             // 204
+	WORLDKEENUR1SPR,             // 205
+	WORLDKEENUR2SPR,             // 206
+	WORLDKEENUR3SPR,             // 207
+	WORLDKEENWAVE1SPR,           // 208
+	WORLDKEENWAVE2SPR,           // 209
+	ROCKETSPR,                   // 210
+	ROCKETFLY1SPR,               // 211
+	ROCKETFLY2SPR,               // 212
+	SATELLITE1SPR,               // 213
+	SATELLITE2SPR,               // 214
+	SATELLITE3SPR,               // 215
+	SATELLITE4SPR,               // 216
+	GRABBITER1SPR,               // 217
+	GRABBITER2SPR,               // 218
+	GRABBITERSLEEP1SPR,          // 219
+	GRABBITERSLEEP2SPR,          // 220
+	WORLDKEENTRHOW1SPR,          // 221
+	WORLDKEENTRHOW2SPR,          // 222
+	WORLDKEENCLIMB1SPR,          // 223
+	WORLDKEENCLIMB2SPR,          // 224
+	ROPETHROW1SPR,               // 225
+	ROPETHROW2SPR,               // 226
+	WORLDKEENHANGSPR,            // 227
+	FLAGFLIP1SPR,                // 228
+	FLAGFLIP2SPR,                // 229
+	FLAGFLIP3SPR,                // 230
+	FLAGFLIP4SPR,                // 231
+	FLAGFLIP5SPR,                // 232
+	FLAGFALL1SPR,                // 233
+	FLAGFALL2SPR,                // 234
+	FLAGFLAP1SPR,                // 235
+	FLAGFLAP2SPR,                // 236
+	FLAGFLAP3SPR,                // 237
+	FLAGFLAP4SPR,                // 238
+	END_LUMP(WORLDKEEN_LUMP_END, __WORLDKEENEND)
+
+	START_LUMP(FLEEX_LUMP_START, __FLEEXSTART)
+	FLEEXWALKR1SPR,              // 239
+	FLEEXWALKR2SPR,              // 240
+	FLEEXWALKL1SPR,              // 241
+	FLEEXWALKL2SPR,              // 242
+	FLEEXLOOK1SPR,               // 243
+	FLEEXLOOK2SPR,               // 244
+	FLEEXSTUNSPR,             // 245
+	END_LUMP(FLEEX_LUMP_END, __FLEEXEND)
+
+	START_LUMP(CEILICK_LUMP_START, __CEILICKSTART)
+	CEILICK1SPR,                 // 246
+	CEILICK2SPR,                 // 247
+	TONGUE1SPR,                  // 248
+	TONGUE2SPR,                  // 249
+	TONGUE3SPR,                  // 250
+	TONGUE4SPR,                  // 251
+	TONGUE5SPR,                  // 252
+	CEILICKSTUNSPR,           // 253
+	END_LUMP(CEILICK_LUMP_END, __CEILICKEND)
+
+	START_LUMP(BLOOGUARD_LUMP_START, __BLOOGUARDSTART)
+	BLOOGUARDWALKL1SPR,          // 254
+	BLOOGUARDWALKL2SPR,          // 255
+	BLOOGUARDWALKL3SPR,          // 256
+	BLOOGUARDWALKL4SPR,          // 257
+	BLOOGUARDWALKR1SPR,          // 258
+	BLOOGUARDWALKR2SPR,          // 259
+	BLOOGUARDWALKR3SPR,          // 260
+	BLOOGUARDWALKR4SPR,          // 261
+	BLOOGUARDSWINGL1SPR,         // 262
+	BLOOGUARDSWINGL2SPR,         // 263
+	BLOOGUARDSWINGL3SPR,         // 264
+	BLOOGUARDSWINGR1SPR,         // 265
+	BLOOGUARDSWINGR2SPR,         // 266
+	BLOOGUARDSWINGR3SPR,         // 267
+	BLOOGUARDSTUNSPR,         // 268
+	END_LUMP(BLOOGUARD_LUMP_END, __BLOOGUARDEND)
+
+	START_LUMP(BIPSHIP_LUMP_START, __BIPSHIPSTART)
+	BIPSHIPRSPR,                 // 269
+	BIPSHIPRTURN1SPR,            // 270
+	BIPSHIPRTURN2SPR,            // 271
+	BIPSHIPRTURN3SPR,            // 272
+	BIPSHIPRTURN4SPR,            // 273
+	BIPSHIPLSPR,                 // 274
+	BIPSHIPLTURN1SPR,            // 275
+	BIPSHIPLTURN2SPR,            // 276
+	BIPSHIPLTURN3SPR,            // 277
+	BIPSHIPLTURN4SPR,            // 278
+	BIPSHIPEXPLODE1SPR,          // 279
+	BIPSHIPEXPLODE2SPR,          // 280
+	BIPSHIPEXPLODE3SPR,          // 281
+	BIPSHIPEXPLODE4SPR,          // 282
+	BIPSHIPEXPLODE5SPR,          // 283
+	BIPSHIPSHOTSPR,              // 284
+	END_LUMP(BIPSHIP_LUMP_END, __BIPSHIPEND)
+
+	START_LUMP(BABOBBA_LUMP_START, __BABOBBASTART)
+	BABOBBAL1SPR,                // 285
+	BABOBBAL2SPR,                // 286
+	BABOBBAL3SPR,                // 287
+	BABOBBAR1SPR,                // 288
+	BABOBBAR2SPR,                // 289
+	BABOBBAR3SPR,                // 290
+	BABOBBASHOT1SPR,             // 291
+	BABOBBASHOT2SPR,             // 292
+	BABOBBASTUNSPR,           // 293
+	BABOBBASLEEP1SPR,            // 294
+	BABOBBASLEEP2SPR,            // 295
+	BABOBBASLEEP3SPR,            // 296
+	BABOBBASLEEP4SPR,            // 297
+	END_LUMP(BABOBBA_LUMP_END, __BABOBBAEND)
+
+	START_LUMP(NOSPIKE_LUMP_START, __NOSPIKESTART)
+	NOSPIKESTANDSPR,             // 298
+	NOSPIKERUNR1SPR,             // 299
+	NOSPIKERUNR2SPR,             // 300
+	NOSPIKERUNR3SPR,             // 301
+	NOSPIKERUNR4SPR,             // 302
+	NOSPIKERUNL1SPR,             // 303
+	NOSPIKERUNL2SPR,             // 304
+	NOSPIKERUNL3SPR,             // 305
+	NOSPIKERUNL4SPR,             // 306
+	NOSPIKEWALKR1SPR,            // 307
+	NOSPIKEWALKR2SPR,            // 308
+	NOSPIKEWALKR3SPR,            // 309
+	NOSPIKEWALKR4SPR,            // 310
+	NOSPIKEWALKL1SPR,            // 311
+	NOSPIKEWALKL2SPR,            // 312
+	NOSPIKEWALKL3SPR,            // 313
+	NOSPIKEWALKL4SPR,            // 314
+	NOSPIKESTUNSPR,           // 315
+	QUESTIONMARKSPR,             // 316
+	END_LUMP(NOSPIKE_LUMP_END, __NOSPIKEEND)
+
+	START_LUMP(FLECT_LUMP_START, __FLECTSTART)
+	FLECTSTANDSPR,               // 317
+	FLECTSTANDRSPR,              // 318
+	FLECTWALKR1SPR,              // 319
+	FLECTWALKR2SPR,              // 320
+	FLECTWALKR3SPR,              // 321
+	FLECTWALKR4SPR,              // 322
+	FLECTSTANDLSPR,              // 323
+	FLECTWALKL1SPR,              // 324
+	FLECTWALKL2SPR,              // 325
+	FLECTWALKL3SPR,              // 326
+	FLECTWALKL4SPR,              // 327
+	FLECTSTUNSPR,             // 328
+	END_LUMP(FLECT_LUMP_END, __FLECTEND)
+
+	START_LUMP(ORBATRIX_LUMP_START, __ORBATRIXSTART)
+	ORBATRIX1SPR,                // 329
+	ORBATRIX2SPR,                // 330
+	ORBATRIX3SPR,                // 331
+	ORBATRIX4SPR,                // 332
+	ORBATRIXL1SPR,               // 333
+	ORBATRIXL2SPR,               // 334
+	ORBATRIXR1SPR,               // 335
+	ORBATRIXR2SPR,               // 336
+	ORBATRIXSPIN1SPR,            // 337
+	ORBATRIXSPIN2SPR,            // 338
+	ORBATRIXSPIN3SPR,            // 339
+	ORBATRIXSPIN4SPR,            // 340
+	ORBATRIXCURLSPR,             // 341
+	END_LUMP(ORBATRIX_LUMP_END, __ORBATRIXEND)
+
+	START_LUMP(BLOOG_LUMP_START, __BLOOGSTART)
+	BLOOGWALKR1SPR,              // 342
+	BLOOGWALKR2SPR,              // 343
+	BLOOGWALKR3SPR,              // 344
+	BLOOGWALKR4SPR,              // 345
+	BLOOGWALKL1SPR,              // 346
+	BLOOGWALKL2SPR,              // 347
+	BLOOGWALKL3SPR,              // 348
+	BLOOGWALKL4SPR,              // 349
+	BLOOGSTUNSPR,             // 350
+	END_LUMP(BLOOG_LUMP_END, __BLOOGEND)
+
+	START_LUMP(RBLOOGLET_LUMP_START, __RBLOOGLETSTART)
+	RBLOOGLETWALKR1SPR,          // 351
+	RBLOOGLETWALKR2SPR,          // 352
+	RBLOOGLETWALKR3SPR,          // 353
+	RBLOOGLETWALKR4SPR,          // 354
+	RBLOOGLETWALKL1SPR,          // 355
+	RBLOOGLETWALKL2SPR,          // 356
+	RBLOOGLETWALKL3SPR,          // 357
+	RBLOOGLETWALKL4SPR,          // 358
+	RBLOOGLETSTUNSPR,         // 359
+	END_LUMP(RBLOOGLET_LUMP_END, __RBLOOGLETEND)
+
+	START_LUMP(YBLOOGLET_LUMP_START, __YBLOOGLETSTART)
+	YBLOOGLETWALKR1SPR,          // 360
+	YBLOOGLETWALKR2SPR,          // 361
+	YBLOOGLETWALKR3SPR,          // 362
+	YBLOOGLETWALKR4SPR,          // 363
+	YBLOOGLETWALKL1SPR,          // 364
+	YBLOOGLETWALKL2SPR,          // 365
+	YBLOOGLETWALKL3SPR,          // 366
+	YBLOOGLETWALKL4SPR,          // 367
+	YBLOOGLETSTUNSPR,         // 368
+	END_LUMP(YBLOOGLET_LUMP_END, __YBLOOGLETEND)
+
+	START_LUMP(BBLOOGLET_LUMP_START, __BBLOOGLETSTART)
+	BBLOOGLETWALKR1SPR,          // 369
+	BBLOOGLETWALKR2SPR,          // 370
+	BBLOOGLETWALKR3SPR,          // 371
+	BBLOOGLETWALKR4SPR,          // 372
+	BBLOOGLETWALKL1SPR,          // 373
+	BBLOOGLETWALKL2SPR,          // 374
+	BBLOOGLETWALKL3SPR,          // 375
+	BBLOOGLETWALKL4SPR,          // 376
+	BBLOOGLETSTUNSPR,         // 377
+	END_LUMP(BBLOOGLET_LUMP_END, __BBLOOGLETEND)
+
+	START_LUMP(GBLOOGLET_LUMP_START, __GBLOOGLETSTART)
+	GBLOOGLETWALKR1SPR,          // 378
+	GBLOOGLETWALKR2SPR,          // 379
+	GBLOOGLETWALKR3SPR,          // 380
+	GBLOOGLETWALKR4SPR,          // 381
+	GBLOOGLETWALKL1SPR,          // 382
+	GBLOOGLETWALKL2SPR,          // 383
+	GBLOOGLETWALKL3SPR,          // 384
+	GBLOOGLETWALKL4SPR,          // 385
+	GBLOOGLETSTUNSPR,         // 386
+	END_LUMP(GBLOOGLET_LUMP_END, __GBLOOGLETEND)
+
+	START_LUMP(GIK_LUMP_START, __GIKSTART)
+	GIKWALKR1SPR,                // 387
+	GIKWALKR2SPR,                // 388
+	GIKWALKR3SPR,                // 389
+	GIKWALKL1SPR,                // 390
+	GIKWALKL2SPR,                // 391
+	GIKWALKL3SPR,                // 392
+	GIKJUMPLSPR,                 // 393
+	GIKJUMPRSPR,                 // 394
+	GIKSLIDER1SPR,               // 395
+	GIKSLIDER2SPR,               // 396
+	GIKSLIDEL1SPR,               // 397
+	GIKSLIDEL2SPR,               // 398
+	END_LUMP(GIK_LUMP_END, __GIKEND)
+
+	START_LUMP(BLORB_LUMP_START, __BLORBSTART)
+	BLORB1SPR,                   // 399
+	BLORB2SPR,                   // 400
+	BLORB3SPR,                   // 401
+	END_LUMP(BLORB_LUMP_END, __BLORBEND)
+
+	START_LUMP(BOBBA_LUMP_START, __BOBBASTART)
+	BOBBAL1SPR,                  // 402
+	BOBBAL2SPR,                  // 403
+	BOBBAL3SPR,                  // 404
+	BOBBAR1SPR,                  // 405
+	BOBBAR2SPR,                  // 406
+	BOBBAR3SPR,                  // 407
+	BOBBASHOT1SPR,               // 408
+	BOBBASHOT2SPR,               // 409
+	BOBBASHOT3SPR,               // 410
+	BOBBASHOT4SPR,               // 411
+	BOBBASHOT5SPR,               // 412
+	BOBBASHOT6SPR,               // 413
+	END_LUMP(BOBBA_LUMP_END, __BOBBAEND)
+
+	START_LUMP(BIP_LUMP_START, __BIPSTART)
+	BIPSTANDSPR,                 // 414
+	BIPWALKR1SPR,                // 415
+	BIPWALKR2SPR,                // 416
+	BIPWALKR3SPR,                // 417
+	BIPWALKR4SPR,                // 418
+	BIPWALKL1SPR,                // 419
+	BIPWALKL2SPR,                // 420
+	BIPWALKL3SPR,                // 421
+	BIPWALKL4SPR,                // 422
+	END_LUMP(BIP_LUMP_END, __BIPEND)
+
+	START_LUMP(BIPSQUISHED_LUMP_START, __BIPSQUISHEDSTART)
+	BIPSQUISHEDSPR,              // 423
+	END_LUMP(BIPSQUISHED_LUMP_END, __BIPSQUISHEDEND)
+
+	START_LUMP(PLATFORM_LUMP_START, __PLATFORMSTART)
+	PLATFORMSPR,                 // 424
+	PLATBIP1SPR,                 // 425
+	PLATBIP2SPR,                 // 426
+	PLATBIP3SPR,                 // 427
+	PLATBIP4SPR,                 // 428
+	PLATBIP5SPR,                 // 429
+	PLATBIP6SPR,                 // 430
+	PLATBIP7SPR,                 // 431
+	PLATBIP8SPR,                 // 432
+	END_LUMP(PLATFORM_LUMP_END, __PLATFORMEND)
+
+	START_LUMP(MOLLY_LUMP_START, __MOLLYSTART)
+	MOLLY1SPR,                   // 433
+	MOLLY2SPR,                   // 434
+	END_LUMP(MOLLY_LUMP_END, __MOLLYEND)
+
+	START_LUMP(PASSCARD_LUMP_START, __PASSCARDSTART)
+	PASSCARDSPR,                 // 435
+	END_LUMP(PASSCARD_LUMP_END, __PASSCARDEND)
+
+	//
+	// TILES (these don't need names)
+	//
+
+	LASTTILE=STARTEXTERNS-1,
+
+	//
+	// EXTERNS
+	//
+
+	T_ENDART,                    // 5550
+
+	ORDERSCREEN,                 // 5551
+	BIGCOMMANDER,                // 5552
+	BIGKEEN,                     // 5553
+	OUTOFMEM,                    // 5554
+
+	//demos
+	DEMO0,                       // 5555
+	DEMO1,                       // 5556
+	DEMO2,                       // 5557
+	DEMO3,                       // 5558
+	DEMO4,                       // 5559
+
+	NUMGRCHUNKS
+} graphicnums;
+
+#undef START_LUMP
+#undef END_LUMP
+
+#endif //__GFX_H__
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/KEEN6/ID_ASM.EQU b/16/keen456/KEEN4-6/KEEN6/ID_ASM.EQU
new file mode 100755
index 00000000..5989f124
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN6/ID_ASM.EQU
@@ -0,0 +1,115 @@
+;
+; Equates for all .ASM files
+;
+
+;----------------------------------------------------------------------------
+
+INCLUDE	"GFXE_CK6.EQU"
+
+;----------------------------------------------------------------------------
+
+CGAGR		=	1
+EGAGR		=	2
+VGAGR		=	3
+
+GRMODE		=	EGAGR
+PROFILE		=	0			; 1=keep stats on tile drawing
+
+SC_INDEX	=	03C4h
+SC_RESET	=	0
+SC_CLOCK	=	1
+SC_MAPMASK	=	2
+SC_CHARMAP	=	3
+SC_MEMMODE	=	4
+
+CRTC_INDEX	=	03D4h
+CRTC_H_TOTAL	=	0
+CRTC_H_DISPEND	=	1
+CRTC_H_BLANK	=	2
+CRTC_H_ENDBLANK	=	3
+CRTC_H_RETRACE	=	4
+CRTC_H_ENDRETRACE =	5
+CRTC_V_TOTAL	=	6
+CRTC_OVERFLOW	=	7
+CRTC_ROWSCAN	=	8
+CRTC_MAXSCANLINE =	9
+CRTC_CURSORSTART =	10
+CRTC_CURSOREND	=	11
+CRTC_STARTHIGH	=	12
+CRTC_STARTLOW	=	13
+CRTC_CURSORHIGH	=	14
+CRTC_CURSORLOW	=	15
+CRTC_V_RETRACE	=	16
+CRTC_V_ENDRETRACE =	17
+CRTC_V_DISPEND	=	18
+CRTC_OFFSET	=	19
+CRTC_UNDERLINE	=	20
+CRTC_V_BLANK	=	21
+CRTC_V_ENDBLANK	=	22
+CRTC_MODE	=	23
+CRTC_LINECOMPARE =	24
+
+
+GC_INDEX	=	03CEh
+GC_SETRESET	=	0
+GC_ENABLESETRESET =	1
+GC_COLORCOMPARE	=	2
+GC_DATAROTATE	=	3
+GC_READMAP	=	4
+GC_MODE		=	5
+GC_MISCELLANEOUS =	6
+GC_COLORDONTCARE =	7
+GC_BITMASK	=	8
+
+ATR_INDEX	=	03c0h
+ATR_MODE	=	16
+ATR_OVERSCAN	=	17
+ATR_COLORPLANEENABLE =	18
+ATR_PELPAN	=	19
+ATR_COLORSELECT	=	20
+
+STATUS_REGISTER_1     =	03dah
+
+
+MACRO	WORDOUT
+	out	dx,ax
+ENDM
+
+if 0
+
+MACRO	WORDOUT
+	out	dx,al
+	inc	dx
+	xchg	al,ah
+	out	dx,al
+	dec	dx
+	xchg	al,ah
+ENDM
+
+endif
+
+UPDATEWIDE	=	22
+UPDATEHIGH	=	14
+
+;
+; tile info offsets from segment tinf
+;
+
+ANIM		=	402
+SPEED		=	(ANIM+NUMTILE16)
+
+NORTHWALL	=	(SPEED+NUMTILE16)
+EASTWALL	=	(NORTHWALL+NUMTILE16M)
+SOUTHWALL   =	(EASTWALL+NUMTILE16M)
+WESTWALL    =	(SOUTHWALL+NUMTILE16M)
+MANIM       =	(WESTWALL+NUMTILE16M)
+INTILE      =	(MANIM+NUMTILE16M)
+MSPEED      =	(INTILE+NUMTILE16M)
+
+
+IFE GRMODE-EGAGR
+SCREENWIDTH	=	64
+ENDIF
+IFE GRMODE-CGAGR
+SCREENWIDTH	=	128
+ENDIF
diff --git a/16/keen456/KEEN4-6/KEEN6/ID_HEADS.H b/16/keen456/KEEN4-6/KEEN6/ID_HEADS.H
new file mode 100755
index 00000000..3a837a49
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN6/ID_HEADS.H
@@ -0,0 +1,109 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+// ID_GLOB.H
+
+
+#include <ALLOC.H>
+#include <CTYPE.H>
+#include <DOS.H>
+#include <ERRNO.H>
+#include <FCNTL.H>
+#include <IO.H>
+#include <MEM.H>
+#include <PROCESS.H>
+#include <STDIO.H>
+#include <STDLIB.H>
+#include <STRING.H>
+#include <SYS\STAT.H>
+
+#define __ID_GLOB__
+
+//--------------------------------------------------------------------------
+
+#define KEEN
+#define KEEN6
+
+#define	EXTENSION	"CK6"
+
+extern	char far introscn;
+
+#include "GFXE_CK6.H"
+#include "AUDIOCK6.H"
+
+//--------------------------------------------------------------------------
+
+#define	TEXTGR	0
+#define	CGAGR	1
+#define	EGAGR	2
+#define	VGAGR	3
+
+#define GRMODE	EGAGR
+
+#if GRMODE == EGAGR
+#define GREXT	"EGA"
+#endif
+#if GRMODE == CGAGR
+#define GREXT	"CGA"
+#endif
+
+//#define PROFILE
+
+//
+//	ID Engine
+//	Types.h - Generic types, #defines, etc.
+//	v1.0d1
+//
+
+#ifndef	__TYPES__
+#define	__TYPES__
+
+typedef	enum	{false,true}	boolean;
+typedef	unsigned	char		byte;
+typedef	unsigned	int			word;
+typedef	unsigned	long		longword;
+typedef	byte *					Ptr;
+
+typedef	struct
+		{
+			int	x,y;
+		} Point;
+typedef	struct
+		{
+			Point	ul,lr;
+		} Rect;
+
+#define	nil	((void *)0)
+
+#endif
+
+#include "ID_MM.H"
+#include "ID_CA.H"
+#include "ID_VW.H"
+#include "ID_RF.H"
+#include "ID_IN.H"
+#include "ID_SD.H"
+#include "ID_US.H"
+
+
+void	Quit (char *error);		// defined in user program
+
diff --git a/16/keen456/KEEN4-6/KEEN6/K6_ACT1.C b/16/keen456/KEEN4-6/KEEN6/K6_ACT1.C
new file mode 100755
index 00000000..a2004bdf
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN6/K6_ACT1.C
@@ -0,0 +1,2137 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+/*
+K6_ACT1.C
+=========
+
+Contains the following actor types (in this order):
+
+- some shared routines
+- Bonus Items
+- Grabbiter
+- Rocket
+- Grapple spots
+- Satellite
+- Quest Items (Sandwich, Grappling Hook, Passcard, Molly)
+- Platforms
+- falling platforms
+- static platforms
+- Goplat platforms
+- Trick platforms
+- Bloog
+- Blooguard
+- Blooglet
+
+*/
+
+#include "CK_DEF.H"
+
+/*
+=============================================================================
+
+						  SHARED STUFF
+
+=============================================================================
+*/
+
+Sint16 pdirx[] = {0, 1, 0, -1, 1, 1, -1, -1};
+Sint16 pdiry[] = {-1, 0, 1, 0, -1, 1, 1, -1};
+
+/*
+===========================
+=
+= C_ClipSide
+=
+===========================
+*/
+
+void C_ClipSide(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		playerkludgeclipcancel = true;
+		ClipToSpriteSide(hit, ob);
+		playerkludgeclipcancel = false;
+	}
+}
+
+/*
+===========================
+=
+= C_ClipTop
+=
+===========================
+*/
+
+void C_ClipTop(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+		ClipToSpriteTop(hit, ob);
+}
+
+/*
+===========================
+=
+= R_Land
+=
+===========================
+*/
+
+void R_Land(objtype *ob)
+{
+	if (ob->hiteast || ob->hitwest)
+		ob->xspeed = 0;
+
+	if (ob->hitsouth)
+		ob->yspeed = 0;
+
+	if (ob->hitnorth)
+	{
+		ob->yspeed = 0;
+		if (ob->state->nextstate)
+		{
+			ChangeState(ob, ob->state->nextstate);
+		}
+		else
+		{
+			RemoveObj(ob);
+			return;
+		}
+	}
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+===========================
+=
+= R_Bounce
+=
+===========================
+*/
+
+void R_Bounce(objtype *ob)
+{
+	Uint16 wall,absx,absy,angle,newangle;
+	Uint32 speed;
+
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+
+	if (ob->hiteast || ob->hitwest)
+		ob->xspeed = -ob->xspeed/2;
+
+	if (ob->hitsouth)
+	{
+		ob->yspeed = -ob->yspeed/2;
+		return;
+	}
+
+	wall = ob->hitnorth;
+#ifdef KEEN6Ev15
+	if (!wall)
+	{
+		return;
+	}
+	else
+#else
+	if (wall)
+#endif
+	{
+		if (ob->yspeed < 0)
+			ob->yspeed = 0;
+
+		absx = abs(ob->xspeed);
+		absy = ob->yspeed;
+		if (absx>absy)
+		{
+			if (absx>absy*2)	// 22 degrees
+			{
+				angle = 0;
+				speed = absx*286;	// x*sqrt(5)/2
+			}
+			else				// 45 degrees
+			{
+				angle = 1;
+				speed = absx*362;	// x*sqrt(2)
+			}
+		}
+		else
+		{
+			if (absy>absx*2)	// 90 degrees
+			{
+				angle = 3;
+				speed = absy*256;
+			}
+			else
+			{
+				angle = 2;		// 67 degrees
+				speed = absy*286;	// y*sqrt(5)/2
+			}
+		}
+		if (ob->xspeed > 0)
+			angle = 7-angle;
+
+		speed >>= 1;
+		newangle = bounceangle[ob->hitnorth][angle];
+		switch (newangle)
+		{
+		case 0:
+			ob->xspeed = speed / 286;
+			ob->yspeed = -ob->xspeed / 2;
+			break;
+		case 1:
+			ob->xspeed = speed / 362;
+			ob->yspeed = -ob->xspeed;
+			break;
+		case 2:
+			ob->yspeed = -(speed / 286);
+			ob->xspeed = -ob->yspeed / 2;
+			break;
+		case 3:
+
+		case 4:
+			ob->xspeed = 0;
+			ob->yspeed = -(speed / 256);
+			break;
+		case 5:
+			ob->yspeed = -(speed / 286);
+			ob->xspeed = ob->yspeed / 2;
+			break;
+		case 6:
+			ob->xspeed = ob->yspeed = -(speed / 362);
+			break;
+		case 7:
+			ob->xspeed = -(speed / 286);
+			ob->yspeed = ob->xspeed / 2;
+			break;
+
+		case 8:
+			ob->xspeed = -(speed / 286);
+			ob->yspeed = -ob->xspeed / 2;
+			break;
+		case 9:
+			ob->xspeed = -(speed / 362);
+			ob->yspeed = -ob->xspeed;
+			break;
+		case 10:
+			ob->yspeed = speed / 286;
+			ob->xspeed = -ob->yspeed / 2;
+			break;
+		case 11:
+
+		case 12:
+			ob->xspeed = 0;
+			ob->yspeed = -(speed / 256);
+			break;
+		case 13:
+			ob->yspeed = speed / 286;
+			ob->xspeed = ob->yspeed / 2;
+			break;
+		case 14:
+			ob->xspeed = speed / 362;
+			ob->yspeed = speed / 362;
+			break;
+		case 15:
+			ob->xspeed = speed / 286;
+			ob->yspeed = ob->xspeed / 2;
+			break;
+		}
+
+		if (speed < 256*16)
+		{
+			ChangeState(ob, ob->state->nextstate);
+		}
+	}
+}
+
+/*
+=============================================================================
+
+						  BONUS ITEMS
+
+temp1 = bonus type
+temp2 = base shape number
+temp3 = last animated shape number +1
+
+=============================================================================
+*/
+
+statetype s_bonus1    = {0, 0, step,      false, false, 20, 0, 0, T_Bonus, NULL, R_Draw, &s_bonus2};
+statetype s_bonus2    = {0, 0, step,      false, false, 20, 0, 0, T_Bonus, NULL, R_Draw, &s_bonus1};
+statetype s_bonusfly1 = {0, 0, stepthink, false, false, 20, 0, 0, T_FlyBonus, NULL, R_Draw, &s_bonusfly2};
+statetype s_bonusfly2 = {0, 0, stepthink, false, false, 20, 0, 0, T_FlyBonus, NULL, R_Draw, &s_bonusfly1};
+statetype s_bonusrise = {0, 0, slide,     false, false, 40, 0, 8, NULL, NULL, R_Draw, NULL};
+
+statetype s_splash1   = {VIVASPLASH1SPR, VIVASPLASH1SPR, step, false, false, 8, 0, 0, NULL, NULL, R_Draw, &s_splash2};
+statetype s_splash2   = {VIVASPLASH2SPR, VIVASPLASH2SPR, step, false, false, 8, 0, 0, NULL, NULL, R_Draw, &s_splash3};
+statetype s_splash3   = {VIVASPLASH3SPR, VIVASPLASH3SPR, step, false, false, 8, 0, 0, NULL, NULL, R_Draw, &s_splash4};
+statetype s_splash4   = {VIVASPLASH4SPR, VIVASPLASH4SPR, step, false, false, 8, 0, 0, NULL, NULL, R_Draw, NULL};
+
+Uint16 bonusshape[] = {
+	REDGEM1SPR, YELLOWGEM1SPR, BLUEGEM1SPR, GREENGEM1SPR,
+	SUGAR1ASPR, SUGAR2ASPR, SUGAR3ASPR,
+	SUGAR4ASPR, SUGAR5ASPR, SUGAR6ASPR,
+	ONEUPASPR, STUNCLIP1SPR
+};
+
+/*
+===========================
+=
+= SpawnBonus
+=
+===========================
+*/
+
+void SpawnBonus(Uint16 tileX, Uint16 tileY, Uint16 type)
+{
+	GetNewObj(false);
+	new->needtoclip = cl_noclip;
+	new->priority = 2;
+	new->obclass = bonusobj;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	new->ydir = -1;
+	new->temp1 = type;
+	new->temp2=new->shapenum = bonusshape[type];
+	new->temp3 = new->temp2+2;
+	NewState(new, &s_bonus1);
+}
+
+/*
+===========================
+=
+= SpawnSplash
+=
+===========================
+*/
+
+void SpawnSplash(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(true);
+	new->needtoclip = cl_noclip;
+	new->priority = 3;
+	new->obclass = inertobj;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	NewState(new, &s_splash1);
+}
+
+/*
+===========================
+=
+= T_Bonus
+=
+===========================
+*/
+
+void T_Bonus(objtype *ob)
+{
+	if (++ob->shapenum == ob->temp3)
+		ob->shapenum = ob->temp2;
+}
+
+/*
+===========================
+=
+= T_FlyBonus
+=
+===========================
+*/
+
+void T_FlyBonus(objtype *ob)
+{
+	if (ob->hitnorth)
+		ob->state = &s_bonus1;
+
+	if (++ob->shapenum == ob->temp3)
+		ob->shapenum = ob->temp2;
+
+	DoGravity(ob);
+}
+
+/*
+=============================================================================
+
+						  GRABBITER
+
+=============================================================================
+*/
+
+statetype s_grabbiter1      = {GRABBITER1SPR,      GRABBITER1SPR,      step, false, false, 12, 0, 0, NULL, C_Grabbiter, R_Draw, &s_grabbiter2};
+statetype s_grabbiter2      = {GRABBITER2SPR,      GRABBITER2SPR,      step, false, false, 12, 0, 0, NULL, C_Grabbiter, R_Draw, &s_grabbiter1};
+statetype s_grabbitersleep1 = {GRABBITERSLEEP1SPR, GRABBITERSLEEP1SPR, step, false, false, 12, 0, 0, NULL, NULL, R_Draw, &s_grabbitersleep2};
+statetype s_grabbitersleep2 = {GRABBITERSLEEP2SPR, GRABBITERSLEEP2SPR, step, false, false, 12, 0, 0, NULL, NULL, R_Draw, &s_grabbitersleep1};
+
+/*
+===========================
+=
+= SpawnGrabbiter
+=
+===========================
+*/
+
+void SpawnGrabbiter(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->active = ac_yes;
+	new->needtoclip = cl_noclip;
+	new->priority = 2;
+	new->obclass = grabbiterobj;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	if (gamestate.sandwichstate == 2)
+	{
+		NewState(new, &s_grabbitersleep1);
+	}
+	else
+	{
+		NewState(new, &s_grabbiter1);
+	}
+}
+
+/*
+===========================
+=
+= C_Grabbiter
+=
+===========================
+*/
+
+void C_Grabbiter(objtype *ob, objtype *hit)
+{
+	// BUG: this is executed for every object, not just (Map-)Keen!
+	switch (gamestate.sandwichstate)
+	{
+	case 0:
+		CA_CacheGrChunk(KEENTALK1PIC);
+		SD_PlaySound(SND_GRABBITER);
+		VW_FixRefreshBuffer();
+		US_CenterWindow(26, 8);
+		VWB_DrawPic(WindowX+WindowW-48, WindowY, KEENTALK1PIC);
+		WindowW -= 48;
+		PrintY += 5;
+		US_CPrint(
+			"Oh, no!\n"
+			"It's a slavering\n"
+			"Grabbiter! He says,\n"
+			"\"Get me lunch and\n"
+			"I'll tell ya a secret!\""
+			);
+		VW_UpdateScreen();
+		SD_PlaySound(SND_NOWAY);
+		VW_WaitVBL(30);
+		IN_ClearKeysDown();
+		IN_Ack();
+		RF_ForceRefresh();
+
+		//push Keen back
+		xtry = -hit->xmove;
+		ytry = -hit->ymove;
+		hit->xdir = hit->ydir = 0;
+		ClipToWalls(hit);
+		break;
+
+	case 1:
+		gamestate.sandwichstate++;
+		CA_CacheGrChunk(KEENTALK1PIC);
+		VW_FixRefreshBuffer();
+		US_CenterWindow(26, 8);
+		VWB_DrawPic(WindowX+WindowW-48, WindowY, KEENTALK1PIC);
+		WindowW -= 48;
+		PrintY += 2;
+		US_CPrint(
+			"The Grabbiter grabs\n"
+			"the gigantic sandwich,\n"
+			"downs it in one bite,\n"
+			"and says,\"Here's your\n"
+			"secret. Big meals\n"
+			"make me sleepy!\n"	// BUG: quote is missing at the end
+			);
+		VW_UpdateScreen();
+		VW_WaitVBL(30);
+		IN_ClearKeysDown();
+		IN_Ack();
+		ChangeState(ob, &s_grabbitersleep1);
+		RF_ForceRefresh();
+	}
+}
+
+/*
+=============================================================================
+
+						  ROCKET
+
+temp1 = direction
+temp2 = countdown to next dir check
+
+=============================================================================
+*/
+
+statetype s_rocket        = {ROCKETSPR,     ROCKETSPR,     think,     false, false, 0, 0, 0, NULL, C_Rocket, R_Draw, NULL};
+statetype s_rocketfly1    = {ROCKETFLY1SPR, ROCKETFLY1SPR, stepthink, false, false, 8, 0, 0, T_RocketFly, C_RocketFly, R_Draw, &s_rocketfly2};
+statetype s_rocketfly2    = {ROCKETFLY2SPR, ROCKETFLY2SPR, stepthink, false, false, 8, 0, 0, T_RocketFly, C_RocketFly, R_Draw, &s_rocketfly1};
+statetype s_keenrocket    = {0,             0,             think,     false, false, 0, 0, 0, T_Rocket, NULL, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnRocket
+=
+===========================
+*/
+
+void SpawnRocket(Uint16 tileX, Uint16 tileY, Uint16 state)
+{
+	if (gamestate.rocketstate == state)
+	{
+		GetNewObj(false);
+		new->active = ac_yes;
+		new->needtoclip = cl_noclip;
+		new->priority = 3;
+		new->obclass = rocketobj;
+		new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+		new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+		NewState(new, &s_rocket);
+	}
+}
+
+/*
+===========================
+=
+= T_Rocket
+=
+===========================
+*/
+
+void T_Rocket(objtype *ob)
+{
+	ob->needtoreact = true;
+}
+
+/*
+===========================
+=
+= C_Rocket
+=
+===========================
+*/
+
+void C_Rocket(objtype *ob, objtype *hit)
+{
+	// BUG: this is executed for every object, not just (Map-)Keen!
+	switch (gamestate.passcardstate)
+	{
+	case 0:
+		CA_CacheGrChunk(KEENTALK1PIC);
+		VW_FixRefreshBuffer();
+		US_CenterWindow(26, 8);
+		VWB_DrawPic(WindowX+WindowW-48, WindowY, KEENTALK1PIC);
+		WindowW -= 48;
+		PrintY += 5;
+		US_CPrint(
+			"The door makes a loud\n"
+			"blooping noise.\n"
+			"It says,\n"
+			"\"Passcard required\n"
+			"for entry.\""
+			);
+		VW_UpdateScreen();
+		SD_PlaySound(SND_NOWAY);
+		VW_WaitVBL(30);
+		IN_ClearKeysDown();
+		IN_Ack();
+		RF_ForceRefresh();
+
+		//push Keen back
+		xtry = -hit->xmove;
+		ytry = -hit->ymove;
+		hit->xdir = hit->ydir = 0;
+		ClipToWalls(hit);
+		break;
+
+	case 1:
+		ob->temp1 = arrow_North;
+		ob->temp2 = TILEGLOBAL;
+		ChangeState(ob, &s_rocketfly1);
+
+		hit->x = ob->x;
+		hit->y = ob->y + TILEGLOBAL;
+		hit->needtoclip = cl_noclip;
+		ChangeState(hit, &s_keenrocket);
+		SD_PlaySound(SND_ROCKETSTART);
+		SD_WaitSoundDone();
+	}
+}
+
+/*
+===========================
+=
+= C_RocketFly
+=
+===========================
+*/
+
+void C_RocketFly(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		hit->x = ob->x;
+		hit->y = ob->y+TILEGLOBAL;
+		ChangeState(hit, hit->state);
+	}
+}
+
+/*
+===========================
+=
+= T_RocketFly
+=
+===========================
+*/
+
+void T_RocketFly(objtype *ob)
+{
+	Uint16 move, tx, ty;
+	Sint16 dir;
+
+	//
+	// this code could be executed twice during the same frame because the
+	// object's animation/state changed during that frame, so don't update
+	// anything if we already have movement for the current frame i.e. the
+	// update code has already been executed this frame
+	//
+	if (xtry == 0 && ytry == 0)
+	{
+		if (!SD_SoundPlaying())
+			SD_PlaySound(SND_ROCKETFLY);
+
+		move = tics << 5;
+		if (ob->temp2 > move)
+		{
+			ob->temp2 = ob->temp2 - move;
+			dir = pdirx[ob->temp1];
+			if (dir == 1)
+			{
+				xtry = move;
+			}
+			else if (dir == -1)
+			{
+				xtry = -move;
+			}
+			dir = pdiry[ob->temp1];
+			if (dir == 1)
+			{
+				ytry = move;
+
+			}
+			else if (dir == -1)
+			{
+				ytry = -move;
+			}
+		}
+		else
+		{
+			dir = pdirx[ob->temp1];
+			if (dir == 1)
+			{
+				xtry = ob->temp2;
+			}
+			else if (dir == -1)
+			{
+				xtry = -ob->temp2;
+			}
+			dir = pdiry[ob->temp1];
+			if (dir == 1)
+			{
+				ytry = ob->temp2;
+			}
+			else if (dir == -1)
+			{
+				ytry = -ob->temp2;
+			}
+
+			tx = CONVERT_GLOBAL_TO_TILE(ob->x + xtry);
+			ty = CONVERT_GLOBAL_TO_TILE(ob->y + ytry);
+			ob->temp1 = *(mapsegs[2]+mapbwidthtable[ty]/2 + tx)-DIRARROWSTART;
+			if (ob->temp1 < arrow_North || ob->temp1 > arrow_None)
+			{
+				ob->x += xtry;
+				ob->y += ytry;
+				ChangeState(ob, &s_rocket);
+
+				player->x = CONVERT_TILE_TO_GLOBAL(tx+1) + 1*PIXGLOBAL;
+				player->y = CONVERT_TILE_TO_GLOBAL(ty+1);
+				player->obclass = keenobj;
+				player->shapenum = WORLDKEENR3SPR;
+				player->needtoclip = cl_midclip;
+				NewState(player, &s_worldkeen);
+				gamestate.rocketstate ^= 1;
+			}
+			else
+			{
+				move -= ob->temp2;
+				ob->temp2 = TILEGLOBAL - move;
+				dir = pdirx[ob->temp1];
+				if (dir == 1)
+				{
+					xtry = xtry + move;
+				}
+				else if (dir == -1)
+				{
+					xtry = xtry - move;
+				}
+				dir = pdiry[ob->temp1];
+				if (dir == 1)
+				{
+					ytry = ytry + move;
+				}
+				else if (dir == -1)
+				{
+					ytry = ytry - move;
+				}
+			}
+		}
+	}
+}
+
+/*
+=============================================================================
+
+						  GRAPPLE SPOT
+
+temp1 = type (0 = top of cliff, 1 = bottom of cliff)
+
+=============================================================================
+*/
+
+statetype s_grapplespot   = {-1,                 -1,                 think, false, false,  0, 0,  0, NULL, C_GrappleSpot, R_Draw, NULL};
+statetype s_throwrope1    = {WORLDKEENTRHOW1SPR, WORLDKEENTRHOW1SPR, step,  false, false, 10, 0,  0, NULL, NULL, R_Draw, &s_throwrope2};
+statetype s_throwrope2    = {WORLDKEENTRHOW2SPR, WORLDKEENTRHOW2SPR, step,  false, false,  8, 0,  0, T_ThrowRope, NULL, R_Draw, &s_worldkeen};
+statetype s_climbrope1    = {WORLDKEENCLIMB1SPR, WORLDKEENCLIMB1SPR, slide, true,  false,  4, 0, 16, NULL, NULL, R_Draw, &s_climbrope2};
+statetype s_climbrope2    = {WORLDKEENCLIMB2SPR, WORLDKEENCLIMB2SPR, slide, true,  false,  4, 0, 16, T_ClimbRope, NULL, R_Draw, &s_climbrope1};
+statetype s_maprope       = {ROPETHROW2SPR,      ROPETHROW2SPR,      think, false, false,  0, 0,  0, NULL, NULL, R_Draw, NULL};
+statetype s_mapropeshort  = {ROPETHROW1SPR,      ROPETHROW1SPR,      step,  false, false, 10, 0,  0, NULL, NULL, R_Draw, &s_mapropeshort};
+
+/*
+===========================
+=
+= SpawnGrappleSpot
+=
+===========================
+*/
+
+void SpawnGrappleSpot(Uint16 tileX, Uint16 tileY, Uint16 type)
+{
+	GetNewObj(false);
+	new->active = ac_yes;
+	new->needtoclip = cl_noclip;
+	new->priority = 2;
+	new->obclass = grapplespotobj;
+	new->tileleft = new->tileright = tileX;
+	new->tiletop = new->tilebottom = tileY;
+	new->temp1 = type;
+	new->x = new->left = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->right = new->left + TILEGLOBAL;
+	if (type)
+	{
+		new->y = new->top = CONVERT_TILE_TO_GLOBAL(tileY+1)-1;
+	}
+	else
+	{
+		new->y = new->top = CONVERT_TILE_TO_GLOBAL(tileY);
+	}
+	new->bottom = new->top + 1;
+	NewState(new, &s_grapplespot);
+
+	if (gamestate.hookstate == 2 && type)
+	{
+		GetNewObj(false);
+		new->active = ac_yes;
+		new->needtoclip = cl_noclip;
+		new->priority = 0;
+		new->obclass = inertobj;
+		new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+		new->y = CONVERT_TILE_TO_GLOBAL(tileY+1);
+		NewState(new, &s_maprope);
+	}
+}
+
+/*
+===========================
+=
+= T_ThrowRope
+=
+===========================
+*/
+
+void T_ThrowRope(objtype *ob)
+{
+	GetNewObj(false);
+	new->active = ac_yes;
+	new->needtoclip = cl_noclip;
+	new->priority = 0;
+	new->obclass = inertobj;
+	new->x = CONVERT_TILE_TO_GLOBAL(ob->tileright);
+	new->y = ob->y - 2*TILEGLOBAL;
+	NewState(new, &s_maprope);
+
+	ob->obclass = keenobj;
+	ob->shapenum = WORLDKEENU3SPR;
+}
+
+/*
+===========================
+=
+= T_ClimbRope
+=
+===========================
+*/
+
+void T_ClimbRope(objtype *ob)
+{
+	if (--ob->temp4 == 0)
+	{
+		if (ob->ydir == 1)
+		{
+			ob->y += 3*PIXGLOBAL;
+			ob->shapenum = WORLDKEEND3SPR;
+		}
+		else
+		{
+			ob->y -= 3*PIXGLOBAL;
+			ob->shapenum = WORLDKEENU3SPR;
+		}
+		ob->obclass = keenobj;
+		NewState(ob, &s_worldkeen);
+	}
+}
+
+/*
+===========================
+=
+= C_GrappleSpot
+=
+===========================
+*/
+
+void C_GrappleSpot(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		switch (gamestate.hookstate)
+		{
+		case 0:
+			CA_CacheGrChunk(KEENTALK1PIC);
+			VW_FixRefreshBuffer();
+			US_CenterWindow(26, 8);
+			VWB_DrawPic(WindowX+WindowW-48, WindowY, KEENTALK1PIC);
+			WindowW -= 48;
+			PrintY += 15;
+			US_CPrint(
+				"What a tall cliff!\n"
+				"Wish I had a rope\n"
+				"and grappling hook.\n"
+				);
+			VW_UpdateScreen();
+			SD_PlaySound(SND_NOWAY);
+			VW_WaitVBL(30);
+			IN_ClearKeysDown();
+			IN_Ack();
+			RF_ForceRefresh();
+
+			//push Keen back
+			xtry = -hit->xmove;
+			ytry = -hit->ymove;
+			hit->xdir = hit->ydir = 0;
+			ClipToWalls(hit);
+			break;
+
+		case 1:
+			gamestate.hookstate++;
+			SD_PlaySound(SND_THROWROPE);
+			ChangeState(hit, &s_throwrope1);
+			hit->obclass = inertobj;
+			break;
+
+		case 2:
+			if (ob->temp1)
+			{
+				hit->y += 4*PIXGLOBAL;
+				hit->temp4 = 6;
+				hit->ydir = 1;
+			}
+			else
+			{
+				hit->y -= 4*PIXGLOBAL;
+				hit->temp4 = 6;
+				hit->ydir = -1;
+			}
+			NewState(hit, &s_climbrope1);
+			hit->obclass = inertobj;
+		}
+	}
+}
+
+/*
+=============================================================================
+
+						  SATELLITE
+
+temp1 = direction (satellite) / type (stop points)
+temp2 = countdown to next dir check
+temp3 = type of stop point touched (low byte: current; high byte: previous)
+        is updated every frame and resets to 0 when no longer touching a spot
+temp4 = type of last stop point passed over (1 or 2, never 0)
+        is updated when no longer touching the spot
+
+=============================================================================
+*/
+
+statetype s_satellitestopspot  = {-1,               -1,               think,     false, false,  0, 0, 0, NULL, NULL, NULL, NULL};
+statetype s_worldkeensatellite = {WORLDKEENHANGSPR, WORLDKEENHANGSPR, think,     false, false,  0, 0, 0, NULL, NULL, R_WorldKeenSatellite, NULL};
+statetype s_satellite1         = {SATELLITE1SPR,    SATELLITE1SPR,    stepthink, false, false, 10, 0, 0, T_Satellite, C_Satellite, R_Draw, &s_satellite2};
+statetype s_satellite2         = {SATELLITE2SPR,    SATELLITE2SPR,    stepthink, false, false, 10, 0, 0, T_Satellite, C_Satellite, R_Draw, &s_satellite3};
+statetype s_satellite3         = {SATELLITE3SPR,    SATELLITE3SPR,    stepthink, false, false, 10, 0, 0, T_Satellite, C_Satellite, R_Draw, &s_satellite4};
+statetype s_satellite4         = {SATELLITE4SPR,    SATELLITE4SPR,    stepthink, false, false, 10, 0, 0, T_Satellite, C_Satellite, R_Draw, &s_satellite1};
+
+/*
+===========================
+=
+= SpawnSatelliteStop
+=
+===========================
+*/
+
+void SpawnSatelliteStop(Uint16 tileX, Uint16 tileY, Uint16 type)
+{
+	GetNewObj(false);
+	new->active = ac_allways;
+	new->needtoclip = cl_noclip;
+	new->priority = 2;
+	new->obclass = satellitestopobj;
+	new->tileleft=new->tileright=tileX;
+	new->tiletop=new->tilebottom=tileY;
+	new->temp1 = (type ^ 1) + 1;	// type is either 0 or 1, so this just maps 0 to 2 and 1 to 1
+	new->x=new->left = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->right = new->left + TILEGLOBAL;
+	new->y=new->top = CONVERT_TILE_TO_GLOBAL(tileY);
+	new->bottom = new->top + TILEGLOBAL;
+	NewState(new, &s_satellitestopspot);
+}
+
+/*
+===========================
+=
+= SpawnSatellite
+=
+===========================
+*/
+
+void SpawnSatellite(Uint16 tileX, Uint16 tileY)
+{
+	Sint16 dir;
+
+	GetNewObj(false);
+	new->needtoclip = cl_noclip;
+	new->priority = 2;
+	new->active = ac_allways;
+	new->obclass = satelliteobj;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	new->xdir = 0;
+	new->ydir = 1;
+	NewState(new, &s_satellite1);
+
+	dir = arrow_West;
+	(mapsegs[2]+mapbwidthtable[tileY]/2)[tileX] = (dir+DIRARROWSTART);
+	new->temp1 = dir;
+	new->temp2 = TILEGLOBAL;
+	new->temp4 = 2;
+}
+
+/*
+===========================
+=
+= T_Satellite
+=
+===========================
+*/
+
+void T_Satellite(objtype *ob)
+{
+	//
+	// this code could be executed twice during the same frame because the
+	// object's animation/state changed during that frame, so don't update
+	// anything if we already have movement for the current frame i.e. the
+	// update code has already been executed this frame
+	//
+	if (xtry == 0 && ytry == 0)
+	{
+		//
+		// if current stop spot type is 0 (not touching a spot), but previous
+		// type is not 0, then set temp4 to the previous type
+		//
+		if (!(ob->temp3 & 0xFF) && (ob->temp3 & 0xFF00))
+		{
+			ob->temp4 = ob->temp3 >> 8;
+		}
+		//
+		// move current type into previous type and set current stop type to 0
+		//
+		ob->temp3 <<= 8;
+
+		//
+		// follow the arrow path like a GoPlat
+		//
+		T_GoPlat(ob);
+	}
+}
+
+/*
+===========================
+=
+= C_Satellite
+=
+===========================
+*/
+
+void C_Satellite(objtype *ob, objtype *hit)
+{
+	Sint16 temp;
+	objtype *o;
+
+	if (hit->state == &s_satellitestopspot)
+	{
+		ob->temp3 |= hit->temp1;
+	}
+	else if (hit->obclass == keenobj)
+	{
+		//
+		// check if satellite has reaced a new stop spot
+		//
+		temp = ob->temp3 >> 8;
+		if (temp && temp != ob->temp4)
+		{
+			SD_PlaySound(SND_GRABSATELLITE);
+			//
+			// update last spot value (don't grab or drop Keen until moved to the next spot)
+			//
+			ob->temp4 = temp;
+			if (player->state == &s_worldkeensatellite)
+			{
+				//
+				// drop Keen off at the current stop spot
+				//
+				for (o=player->next; o; o=o->next)
+				{
+					if (o->obclass == satellitestopobj && o->temp1 == temp)
+					{
+						hit->x = o->x;
+						hit->y = o->y;
+						hit->shapenum = WORLDKEENU3SPR;
+						ChangeState(player, &s_worldkeen);
+						hit->needtoclip = cl_midclip;
+						return;
+					}
+				}
+			}
+			else
+			{
+				//
+				// grab and carry Keen
+				//
+				hit->x = ob->x + 12*PIXGLOBAL;
+				hit->y = ob->y + 16*PIXGLOBAL;
+				hit->needtoclip = cl_noclip;
+				ChangeState(player, &s_worldkeensatellite);
+			}
+		}
+		else if (hit->state == &s_worldkeensatellite)
+		{
+			//
+			// move Keen along with the satellite
+			//
+			hit->x = ob->x + 12*PIXGLOBAL;
+			hit->y = ob->y + 16*PIXGLOBAL;
+			ChangeState(hit, hit->state);
+		}
+	}
+}
+
+/*
+===========================
+=
+= R_WorldKeenSatellite
+=
+===========================
+*/
+
+void R_WorldKeenSatellite(objtype *ob)
+{
+	RF_PlaceSprite(&ob->sprite, ob->x + 4*PIXGLOBAL, ob->y + 8*PIXGLOBAL, WORLDKEENHANGSPR, spritedraw, 1);
+}
+
+/*
+=============================================================================
+
+						  SANDWICH
+
+=============================================================================
+*/
+
+statetype s_sandwich      = {SANDWICHSPR, SANDWICHSPR, think, false, false, 0, 0, 0, NULL, C_Molly, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnSandwich
+=
+===========================
+*/
+
+void SpawnSandwich(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->needtoclip = cl_noclip;
+	new->priority = 2;
+	new->obclass = sandwichobj;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	NewState(new, &s_sandwich);
+}
+
+/*
+=============================================================================
+
+						  GRAPPLING HOOK
+
+=============================================================================
+*/
+
+statetype s_hook          = {HOOKSPR, HOOKSPR, think, false, false, 0, 0, 0, NULL, C_Molly, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnHook
+=
+===========================
+*/
+
+void SpawnHook(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->needtoclip = cl_noclip;
+	new->priority = 2;
+	new->obclass = hookobj;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	NewState(new, &s_hook);
+}
+
+/*
+=============================================================================
+
+						  PASSCARD
+
+=============================================================================
+*/
+
+statetype s_passcard      = {PASSCARDSPR, PASSCARDSPR, think, false, false, 0, 0, 0, NULL, C_Molly, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnPasscard
+=
+===========================
+*/
+
+void SpawnPasscard(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->needtoclip = cl_noclip;
+	new->priority = 2;
+	new->obclass = passcardobj;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	NewState(new, &s_passcard);
+}
+
+//============================================================================
+
+/*
+===========================
+=
+= C_Molly
+=
+===========================
+*/
+
+void C_Molly(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		switch (ob->obclass)
+		{
+		case sandwichobj:
+			playstate = ex_sandwich;
+			break;
+
+		case hookobj:
+			playstate = ex_hook;
+			break;
+
+		case passcardobj:
+			playstate = ex_card;
+			break;
+
+		case mollyobj:
+			playstate = ex_molly;
+		}
+	}
+}
+
+/*
+=============================================================================
+
+						  MOLLY
+
+=============================================================================
+*/
+
+statetype s_molly1        = {MOLLY1SPR, MOLLY1SPR, step, false, false, 20, 0, 0, NULL, C_Molly, R_Draw, &s_molly2};
+statetype s_molly2        = {MOLLY2SPR, MOLLY2SPR, step, false, false, 40, 0, 0, NULL, C_Molly, R_Draw, &s_molly3};
+statetype s_molly3        = {MOLLY1SPR, MOLLY1SPR, step, false, false, 40, 0, 0, NULL, C_Molly, R_Draw, &s_molly4};
+statetype s_molly4        = {MOLLY2SPR, MOLLY2SPR, step, false, false, 20, 0, 0, NULL, C_Molly, R_Draw, &s_molly1};
+
+/*
+===========================
+=
+= SpawnMolly
+=
+===========================
+*/
+
+void SpawnMolly(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = mollyobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -8*PIXGLOBAL;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	NewState(new, &s_molly1);
+}
+
+/*
+=============================================================================
+
+						  PLATFORM
+
+=============================================================================
+*/
+
+statetype s_platform      = {PLATFORMSPR, PLATFORMSPR, think, false, false, 0, 0, 0, T_Platform, NULL, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnPlatform
+=
+===========================
+*/
+
+void SpawnPlatform(Uint16 tileX, Uint16 tileY, Sint16 dir)
+{
+	GetNewObj(false);
+	new->obclass = platformobj;
+	new->active = ac_allways;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	switch (dir)
+	{
+	case 0:
+		new->xdir = 0;
+		new->ydir = -1;
+		break;
+	case 1:
+		new->xdir = 1;
+		new->ydir = 0;
+		break;
+	case 2:
+		new->xdir = 0;
+		new->ydir = 1;
+		break;
+	case 3:
+		new->xdir = -1;
+		new->ydir = 0;
+	}
+	NewState(new, &s_platform);
+}
+
+/*
+===========================
+=
+= T_Platform
+=
+===========================
+*/
+
+void T_Platform(objtype *ob)
+{
+	Uint16 newpos, newtile;
+
+	xtry = ob->xdir * 12 * tics;
+	ytry = ob->ydir * 12 * tics;
+
+	if (ob->xdir == 1)
+	{
+		newpos = ob->right + xtry;
+		newtile = CONVERT_GLOBAL_TO_TILE(newpos);
+		if (ob->tileright != newtile)
+		{
+			if (*(mapsegs[2]+mapbwidthtable[ob->tiletop]/2 + newtile) == PLATFORMBLOCK)
+			{
+				ob->xdir = -1;
+				xtry = xtry - (newpos & 0xFF);
+			}
+		}
+	}
+	else if (ob->xdir == -1)
+	{
+		newpos = ob->left + xtry;
+		newtile = CONVERT_GLOBAL_TO_TILE(newpos);
+		if (ob->tileleft != newtile)
+		{
+			if (*(mapsegs[2]+mapbwidthtable[ob->tiletop]/2 + newtile) == PLATFORMBLOCK)
+			{
+				ob->xdir = 1;
+				xtry = xtry + (TILEGLOBAL - (newpos & 0xFF));
+			}
+		}
+	}
+	else if (ob->ydir == 1)
+	{
+		newpos = ob->bottom + ytry;
+		newtile = CONVERT_GLOBAL_TO_TILE(newpos);
+		if (ob->tilebottom != newtile)
+		{
+			if (*(mapsegs[2]+mapbwidthtable[newtile]/2 + ob->tileleft) == PLATFORMBLOCK)
+			{
+				if (*(mapsegs[2]+mapbwidthtable[newtile-2]/2 + ob->tileleft) == PLATFORMBLOCK)
+				{
+					ytry = 0;
+					ob->needtoreact = true;
+				}
+				else
+				{
+					ob->ydir = -1;
+					ytry = ytry - (newpos & 0xFF);
+				}
+			}
+		}
+	}
+	else if (ob->ydir == -1)
+	{
+		newpos = ob->top + ytry;
+		newtile = CONVERT_GLOBAL_TO_TILE(newpos);
+		if (ob->tiletop != newtile)
+		{
+			if (*(mapsegs[2]+mapbwidthtable[newtile]/2 + ob->tileleft) == PLATFORMBLOCK)
+			{
+				if (*(mapsegs[2]+mapbwidthtable[newtile+2]/2 + ob->tileleft) == PLATFORMBLOCK)
+				{
+					ytry = 0;
+					ob->needtoreact = true;
+				}
+				else
+				{
+					ob->ydir = 1;
+					ytry = ytry + (TILEGLOBAL - (newpos & 0xFF));
+				}
+			}
+		}
+	}
+}
+
+/*
+=============================================================================
+
+						  DROPPING PLATFORM
+
+temp1 = initial y position
+
+=============================================================================
+*/
+
+statetype s_dropplatsit  = {PLATFORMSPR, PLATFORMSPR, think,      false, false, 0, 0,   0, T_DropPlatSit, NULL, R_Draw, NULL};
+statetype s_fallplatfall = {PLATFORMSPR, PLATFORMSPR, think,      false, false, 0, 0,   0, T_DropPlatFall, NULL, R_Draw, NULL};
+statetype s_fallplatrise = {PLATFORMSPR, PLATFORMSPR, slidethink, false, false, 0, 0, -32, T_DropPlatRise, NULL, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnDropPlat
+=
+===========================
+*/
+
+void SpawnDropPlat(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = platformobj;
+	new->active = ac_allways;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y=new->temp1 = CONVERT_TILE_TO_GLOBAL(tileY);
+	new->xdir = 0;
+	new->ydir = 1;
+	new->needtoclip = cl_noclip;
+	NewState(new, &s_dropplatsit);
+}
+
+/*
+===========================
+=
+= T_DropPlatSit
+=
+===========================
+*/
+
+void T_DropPlatSit(objtype *ob)
+{
+	if (gamestate.riding == ob)
+	{
+		ytry = tics << 4;	//tics * 16;
+		ob->yspeed = 0;
+		if (ob->y + ytry - ob->temp1 >= 8*PIXGLOBAL)
+			ob->state = &s_fallplatfall;
+	}
+}
+
+/*
+===========================
+=
+= T_DropPlatFall
+=
+===========================
+*/
+
+void T_DropPlatFall(objtype *ob)
+{
+	Uint16 newpos, newtile;
+
+	DoGravity(ob);
+
+#if 0
+	// bugfix: don't skip a tile (this is present in Keen 4, but missing in 5 & 6)
+	if (ytry >= 15*PIXGLOBAL)
+		ytry = 15*PIXGLOBAL;
+#endif
+
+	newpos = ob->bottom + ytry;
+	newtile = CONVERT_GLOBAL_TO_TILE(newpos);
+	if (ob->tilebottom != newtile)
+	{
+		if (*(mapsegs[2]+mapbwidthtable[newtile]/2 + ob->tileleft) == PLATFORMBLOCK)
+		{
+			ytry = 0xFF - (ob->bottom & 0xFF);
+			if (gamestate.riding != ob)
+				ob->state = &s_fallplatrise;
+		}
+	}
+}
+
+/*
+===========================
+=
+= T_DropPlatRise
+=
+===========================
+*/
+
+void T_DropPlatRise(objtype *ob)
+{
+	if (gamestate.riding == ob)
+	{
+		ob->yspeed = 0;
+		ob->state = &s_fallplatfall;
+	}
+	else if (ob->y <= ob->temp1)
+	{
+		ytry = ob->temp1 - ob->y;
+		ob->state = &s_dropplatsit;
+	}
+}
+
+/*
+=============================================================================
+
+						  STATIC PLATFORM
+
+temp1 = initial y position (is set but never used)
+
+=============================================================================
+*/
+
+statetype s_staticplatform = {PLATFORMSPR, PLATFORMSPR, step, false, false, 32000, 0, 0, NULL, NULL, R_Draw, &s_staticplatform};
+
+/*
+===========================
+=
+= SpawnStaticPlat
+=
+===========================
+*/
+
+void SpawnStaticPlat(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = platformobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y=new->temp1 = CONVERT_TILE_TO_GLOBAL(tileY);
+	new->xdir = 0;
+	new->ydir = 1;
+	new->needtoclip = cl_noclip;
+	NewState(new, &s_staticplatform);
+}
+
+/*
+=============================================================================
+
+						  GO PLATFORM
+
+temp1 = direction
+temp2 = countdown to next dir check
+temp3 = sprite pointer for the Bip sprite
+
+=============================================================================
+*/
+
+statetype s_goplat        = {PLATFORMSPR, PLATFORMSPR, think, false, false, 0, 0, 0, T_GoPlat, NULL, R_GoPlat, NULL};
+
+/*
+===========================
+=
+= SpawnGoPlat
+=
+===========================
+*/
+
+void SpawnGoPlat(Uint16 tileX, Uint16 tileY, Sint16 dir)
+{
+	GetNewObj(false);
+	new->obclass = platformobj;
+	new->active = ac_allways;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	new->xdir = 0;
+	new->ydir = 1;
+	new->needtoclip = cl_noclip;
+	NewState(new, &s_goplat);
+	*(mapsegs[2]+mapbwidthtable[tileY]/2 + tileX) = dir + DIRARROWSTART;
+	new->temp1 = dir;
+	new->temp2 = TILEGLOBAL;
+}
+
+/*
+===========================
+=
+= T_GoPlat
+=
+===========================
+*/
+
+void T_GoPlat(objtype *ob)
+{
+	Uint16 move;
+	Sint16 dir;
+	Uint16 tx, ty;
+
+	move = tics * 12;
+	if (ob->temp2 > move)
+	{
+		ob->temp2 = ob->temp2 - move;
+
+		dir = pdirx[ob->temp1];
+		if (dir == 1)
+		{
+			xtry = xtry + move;
+		}
+		else if (dir == -1)
+		{
+			xtry = xtry + -move;
+		}
+
+		dir = pdiry[ob->temp1];
+		if (dir == 1)
+		{
+			ytry = ytry + move;
+		}
+		else if (dir == -1)
+		{
+			ytry = ytry + -move;
+		}
+	}
+	else
+	{
+		dir = pdirx[ob->temp1];
+		if (dir == 1)
+		{
+			xtry += ob->temp2;
+		}
+		else if (dir == -1)
+		{
+			xtry += -ob->temp2;
+		}
+
+		dir = pdiry[ob->temp1];
+		if (dir == 1)
+		{
+			ytry += ob->temp2;
+		}
+		else if (dir == -1)
+		{
+			ytry += -ob->temp2;
+		}
+
+		tx = CONVERT_GLOBAL_TO_TILE(ob->x + xtry);
+		ty = CONVERT_GLOBAL_TO_TILE(ob->y + ytry);
+		ob->temp1 = *(mapsegs[2]+mapbwidthtable[ty]/2 + tx) - DIRARROWSTART;
+		if (ob->temp1 < arrow_North || ob->temp1 > arrow_None)
+		{
+			Quit("Goplat moved to a bad spot!");
+		}
+
+		move -= ob->temp2;
+		ob->temp2 = TILEGLOBAL - move;
+
+		dir = pdirx[ob->temp1];
+		if (dir == 1)
+		{
+			xtry = xtry + move;
+		}
+		else if (dir == -1)
+		{
+			xtry = xtry - move;
+		}
+
+		dir = pdiry[ob->temp1];
+		if (dir == 1)
+		{
+			ytry = ytry + move;
+		}
+		else if (dir == -1)
+		{
+			ytry = ytry - move;
+		}
+	}
+}
+
+/*
+===========================
+=
+= R_GoPlat
+=
+===========================
+*/
+
+void R_GoPlat(objtype *ob)
+{
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+	RF_PlaceSprite((void**)&ob->temp3, ob->x+TILEGLOBAL, ob->y+TILEGLOBAL, ob->temp1+PLATBIP1SPR, spritedraw, ob->priority);
+}
+
+/*
+=============================================================================
+
+						  SNEAKY PLATFORM
+
+temp1 = initial x position (is set but never used)
+
+=============================================================================
+*/
+
+statetype s_sneakplatsit    = {PLATFORMSPR, PLATFORMSPR, think, false, false,  0,   0, 0, T_SneakPlat, NULL, R_Draw, NULL};
+statetype s_sneakplatdodge  = {PLATFORMSPR, PLATFORMSPR, slide, false, false, 48,  32, 0, NULL, NULL, R_Draw, &s_sneakplatreturn};
+statetype s_sneakplatreturn = {PLATFORMSPR, PLATFORMSPR, slide, false, false, 96, -16, 0, NULL, NULL, R_Draw, &s_sneakplatsit};
+
+/*
+===========================
+=
+= SpawnSneakPlat
+=
+===========================
+*/
+
+void SpawnSneakPlat(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = platformobj;
+	new->active = ac_allways;
+	new->priority = 0;
+	new->x=new->temp1 = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	new->xdir = 0;
+	new->ydir = 1;
+	new->needtoclip = cl_noclip;
+	NewState(new, &s_sneakplatsit);
+}
+
+/*
+===========================
+=
+= T_SneakPlat
+=
+===========================
+*/
+
+void T_SneakPlat(objtype *ob)
+{
+	Sint16 dist;
+
+	if (player->state != &s_keenjump1)
+		return;
+
+	if (player->xdir == 1)
+	{
+		dist = ob->left-player->right;
+		if (dist > 4*TILEGLOBAL || dist < 0)
+			return;
+	}
+	else
+	{
+		dist = player->left-ob->right;
+		if (dist > 4*TILEGLOBAL || dist < 0)
+			return;
+	}
+
+	dist = player->y - ob->y;
+	if (dist < -6*TILEGLOBAL || dist > 6*TILEGLOBAL)
+		return;
+
+	ob->xdir = player->xdir;
+	ob->state = &s_sneakplatdodge;
+}
+
+/*
+=============================================================================
+
+						  BLOOG
+
+=============================================================================
+*/
+
+statetype s_bloogwalk1 = {BLOOGWALKL1SPR, BLOOGWALKR1SPR, step,  false, true, 10, 128, 0, T_BloogWalk, C_Bloog, R_Walk, &s_bloogwalk2};
+statetype s_bloogwalk2 = {BLOOGWALKL2SPR, BLOOGWALKR2SPR, step,  false, true, 10, 128, 0, T_BloogWalk, C_Bloog, R_Walk, &s_bloogwalk3};
+statetype s_bloogwalk3 = {BLOOGWALKL3SPR, BLOOGWALKR3SPR, step,  false, true, 10, 128, 0, T_BloogWalk, C_Bloog, R_Walk, &s_bloogwalk4};
+statetype s_bloogwalk4 = {BLOOGWALKL4SPR, BLOOGWALKR4SPR, step,  false, true, 10, 128, 0, T_BloogWalk, C_Bloog, R_Walk, &s_bloogwalk1};
+statetype s_bloogstun  = {BLOOGSTUNSPR,   BLOOGSTUNSPR,   think, false, false, 0,   0, 0, T_Projectile, NULL, R_Stunned, &s_bloogstun};
+
+/*
+===========================
+=
+= SpawnBloog
+=
+===========================
+*/
+
+void SpawnBloog(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = bloogobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -2*TILEGLOBAL;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	NewState(new, &s_bloogwalk1);
+}
+
+/*
+===========================
+=
+= T_BloogWalk
+=
+===========================
+*/
+
+void T_BloogWalk(objtype *ob)
+{
+	if (US_RndT() < 0x20)
+	{
+		if (ob->x < player->x)
+		{
+			ob->xdir = 1;
+		}
+		else
+		{
+			ob->xdir = -1;
+		}
+	}
+}
+
+/*
+===========================
+=
+= C_Bloog
+=
+===========================
+*/
+
+void C_Bloog(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+	else if (hit->obclass == stunshotobj)
+	{
+		StunObj(ob, hit, &s_bloogstun);
+	}
+}
+
+/*
+=============================================================================
+
+						  BLOOGUARD
+
+temp1 = flash countdown
+temp2 = health
+
+=============================================================================
+*/
+
+statetype s_blooguardwalk1   = {BLOOGUARDWALKL1SPR,  BLOOGUARDWALKR1SPR,  step,  false, true,  9, 128, 0, T_BlooguardWalk, C_Blooguard, R_Blooguard, &s_blooguardwalk2};
+statetype s_blooguardwalk2   = {BLOOGUARDWALKL2SPR,  BLOOGUARDWALKR2SPR,  step,  false, true,  9, 128, 0, T_BlooguardWalk, C_Blooguard, R_Blooguard, &s_blooguardwalk3};
+statetype s_blooguardwalk3   = {BLOOGUARDWALKL3SPR,  BLOOGUARDWALKR3SPR,  step,  false, true,  9, 128, 0, T_BlooguardWalk, C_Blooguard, R_Blooguard, &s_blooguardwalk4};
+statetype s_blooguardwalk4   = {BLOOGUARDWALKL4SPR,  BLOOGUARDWALKR4SPR,  step,  false, true,  9, 128, 0, T_BlooguardWalk, C_Blooguard, R_Blooguard, &s_blooguardwalk1};
+statetype s_blooguardattack1 = {BLOOGUARDSWINGL1SPR, BLOOGUARDSWINGR1SPR, step,  false, true, 30,   0, 0, NULL, C_Blooguard, R_Blooguard, &s_blooguardattack2};
+statetype s_blooguardattack2 = {BLOOGUARDSWINGL2SPR, BLOOGUARDSWINGR2SPR, step,  false, true,  9,   0, 0, NULL, C_Blooguard, R_Blooguard, &s_blooguardattack3};
+statetype s_blooguardattack3 = {BLOOGUARDSWINGL3SPR, BLOOGUARDSWINGR3SPR, step,  true,  true,  1,   0, 0, T_BlooguardAttack, C_Blooguard, R_Blooguard, &s_blooguardattack4};
+statetype s_blooguardattack4 = {BLOOGUARDSWINGL3SPR, BLOOGUARDSWINGR3SPR, step,  false, true,  9,   0, 0, NULL, C_Blooguard, R_Blooguard, &s_blooguardwalk1};
+statetype s_blooguardstun    = {BLOOGUARDSTUNSPR,    BLOOGUARDSTUNSPR,    think, false, false, 0,   0, 0, T_Projectile, NULL, R_Stunned, &s_blooguardstun};
+
+/*
+===========================
+=
+= SpawnBlooguard
+=
+===========================
+*/
+
+void SpawnBlooguard(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = blooguardobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -40*PIXGLOBAL;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	new->temp2 = 3;	// health
+	NewState(new, &s_blooguardwalk1);
+}
+
+/*
+===========================
+=
+= T_BlooguardWalk
+=
+===========================
+*/
+
+void T_BlooguardWalk(objtype *ob)
+{
+	if (US_RndT() < 0x20)
+	{
+		if (ob->x < player->x)
+		{
+			ob->xdir = 1;
+		}
+		else
+		{
+			ob->xdir = -1;
+		}
+	}
+	if ( ((ob->xdir == 1 && ob->x < player->x) || (ob->xdir == -1 && ob->x > player->x))
+		&& ob->bottom == player->bottom && US_RndT() < 0x20)
+	{
+		ob->state = &s_blooguardattack1;
+	}
+}
+
+/*
+===========================
+=
+= T_BlooguardAttack
+=
+===========================
+*/
+
+#pragma argsused
+void T_BlooguardAttack(objtype *ob)
+{
+	SD_PlaySound(SND_SMASH);
+	groundslam = 23;
+	if (player->hitnorth)
+	{
+		ChangeState(player, &s_keenstun);
+	}
+}
+
+/*
+===========================
+=
+= C_Blooguard
+=
+===========================
+*/
+
+void C_Blooguard(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+	if (hit->obclass == stunshotobj)	// not 'else if' in the original code
+	{
+		if (--ob->temp2 == 0)	// handle health
+		{
+			StunObj(ob, hit, &s_blooguardstun);
+		}
+		else
+		{
+			ob->temp1 = 2;	// draw white twice
+			ob->needtoreact = true;
+			ExplodeShot(hit);
+		}
+	}
+}
+
+/*
+===========================
+=
+= R_Blooguard
+=
+===========================
+*/
+
+void R_Blooguard(objtype *ob)
+{
+	if (ob->xdir == 1 && ob->hitwest)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = -1;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	else if (ob->xdir == -1 && ob->hiteast)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = 1;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	else if (!ob->hitnorth)
+	{
+		ob->x -= ob->xmove*2;
+		ob->xdir = -ob->xdir;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	if (ob->temp1)
+	{
+		ob->temp1--;
+		RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, maskdraw, ob->priority);
+	}
+	else
+	{
+		RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+	}
+}
+
+/*
+=============================================================================
+
+						  BLOOGLET
+
+temp1 = type
+
+=============================================================================
+*/
+
+// red Blooglet:
+statetype s_rbloogletwalk1 = {RBLOOGLETWALKL1SPR, RBLOOGLETWALKR1SPR, step,  false, true,  5, 128, 0, T_BloogWalk, C_Blooglet, R_Walk, &s_rbloogletwalk2};
+statetype s_rbloogletwalk2 = {RBLOOGLETWALKL2SPR, RBLOOGLETWALKR2SPR, step,  false, true,  5, 128, 0, T_BloogWalk, C_Blooglet, R_Walk, &s_rbloogletwalk3};
+statetype s_rbloogletwalk3 = {RBLOOGLETWALKL3SPR, RBLOOGLETWALKR3SPR, step,  false, true,  5, 128, 0, T_BloogWalk, C_Blooglet, R_Walk, &s_rbloogletwalk4};
+statetype s_rbloogletwalk4 = {RBLOOGLETWALKL4SPR, RBLOOGLETWALKR4SPR, step,  false, true,  5, 128, 0, T_BloogWalk, C_Blooglet, R_Walk, &s_rbloogletwalk1};
+statetype s_rbloogletstun  = {RBLOOGLETSTUNSPR,   RBLOOGLETSTUNSPR,   think, false, false, 0,   0, 0, T_Projectile, NULL, R_Stunned, NULL};
+
+// yellow Blooglet:
+statetype s_ybloogletwalk1 = {YBLOOGLETWALKL1SPR, YBLOOGLETWALKR1SPR, step,  false, true,  5, 128, 0, T_BloogWalk, C_Blooglet, R_Walk, &s_ybloogletwalk2};
+statetype s_ybloogletwalk2 = {YBLOOGLETWALKL2SPR, YBLOOGLETWALKR2SPR, step,  false, true,  5, 128, 0, T_BloogWalk, C_Blooglet, R_Walk, &s_ybloogletwalk3};
+statetype s_ybloogletwalk3 = {YBLOOGLETWALKL3SPR, YBLOOGLETWALKR3SPR, step,  false, true,  5, 128, 0, T_BloogWalk, C_Blooglet, R_Walk, &s_ybloogletwalk4};
+statetype s_ybloogletwalk4 = {YBLOOGLETWALKL4SPR, YBLOOGLETWALKR4SPR, step,  false, true,  5, 128, 0, T_BloogWalk, C_Blooglet, R_Walk, &s_ybloogletwalk1};
+statetype s_ybloogletstun  = {YBLOOGLETSTUNSPR,   YBLOOGLETSTUNSPR,   think, false, false, 0,   0, 0, T_Projectile, NULL, R_Stunned, NULL};
+
+// blue Blooglet:
+statetype s_bbloogletwalk1 = {BBLOOGLETWALKL1SPR, BBLOOGLETWALKR1SPR, step,  false, true,  5, 128, 0, T_BloogWalk, C_Blooglet, R_Walk, &s_bbloogletwalk2};
+statetype s_bbloogletwalk2 = {BBLOOGLETWALKL2SPR, BBLOOGLETWALKR2SPR, step,  false, true,  5, 128, 0, T_BloogWalk, C_Blooglet, R_Walk, &s_bbloogletwalk3};
+statetype s_bbloogletwalk3 = {BBLOOGLETWALKL3SPR, BBLOOGLETWALKR3SPR, step,  false, true,  5, 128, 0, T_BloogWalk, C_Blooglet, R_Walk, &s_bbloogletwalk4};
+statetype s_bbloogletwalk4 = {BBLOOGLETWALKL4SPR, BBLOOGLETWALKR4SPR, step,  false, true,  5, 128, 0, T_BloogWalk, C_Blooglet, R_Walk, &s_bbloogletwalk1};
+statetype s_bbloogletstun  = {BBLOOGLETSTUNSPR,   BBLOOGLETSTUNSPR,   think, false, false, 0,   0, 0, T_Projectile, NULL, R_Stunned, NULL};
+
+// green Blooglet:
+statetype s_gbloogletwalk1 = {GBLOOGLETWALKL1SPR, GBLOOGLETWALKR1SPR, step,  false, true,  5, 128, 0, T_BloogWalk, C_Blooglet, R_Walk, &s_gbloogletwalk2};
+statetype s_gbloogletwalk2 = {GBLOOGLETWALKL2SPR, GBLOOGLETWALKR2SPR, step,  false, true,  5, 128, 0, T_BloogWalk, C_Blooglet, R_Walk, &s_gbloogletwalk3};
+statetype s_gbloogletwalk3 = {GBLOOGLETWALKL3SPR, GBLOOGLETWALKR3SPR, step,  false, true,  5, 128, 0, T_BloogWalk, C_Blooglet, R_Walk, &s_gbloogletwalk4};
+statetype s_gbloogletwalk4 = {GBLOOGLETWALKL4SPR, GBLOOGLETWALKR4SPR, step,  false, true,  5, 128, 0, T_BloogWalk, C_Blooglet, R_Walk, &s_gbloogletwalk1};
+statetype s_gbloogletstun  = {GBLOOGLETSTUNSPR,   GBLOOGLETSTUNSPR,   think, false, false, 0,   0, 0, T_Projectile, NULL, R_Stunned, NULL};
+
+/*
+===========================
+=
+= SpawnBlooglet
+=
+===========================
+*/
+
+void SpawnBlooglet(Uint16 tileX, Uint16 tileY, Sint16 type)
+{
+	GetNewObj(false);
+	new->obclass = bloogletobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -8*PIXGLOBAL;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	new->temp1 = type;
+
+	switch (type % 4)
+	{
+	case 0:
+		NewState(new, &s_rbloogletwalk1);
+		break;
+
+	case 1:
+		NewState(new, &s_ybloogletwalk1);
+		break;
+
+	case 2:
+		NewState(new, &s_bbloogletwalk1);
+		break;
+
+	case 3:
+		NewState(new, &s_gbloogletwalk1);
+	}
+}
+
+/*
+===========================
+=
+= C_Blooglet
+=
+===========================
+*/
+
+void C_Blooglet(objtype *ob, objtype *hit)
+{
+	static statetype *stunnedstate[4] = {
+		&s_rbloogletstun,
+		&s_ybloogletstun,
+		&s_bbloogletstun,
+		&s_gbloogletstun
+	};
+	Sint16 color;
+
+	if (hit->obclass == keenobj && hit->state->contact)
+	{
+		playerkludgeclipcancel = true;
+		ClipToSpriteSide(hit, ob);
+		playerkludgeclipcancel = false;
+	}
+	else if (hit->obclass == stunshotobj)
+	{
+		color = ob->temp1 & 3;
+		if (ob->temp1 > 3)
+		{
+			//
+			// spawn a key gem
+			//
+			GetNewObj(false);
+			new->needtoclip = cl_midclip;
+			new->priority = 2;
+			new->obclass = bonusobj;
+			new->x = ob->x;
+			new->y = ob->y;
+			new->ydir = -1;
+			new->yspeed = -40;
+			new->temp1 = color;
+			new->temp2=new->shapenum = bonusshape[color];
+			new->temp3 = new->temp2 + 2;
+			NewState(new, &s_bonusfly1);
+			SD_PlaySound(SND_DROPKEY);
+		}
+		StunObj(ob, hit, stunnedstate[color]);
+	}
+}
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/KEEN6/K6_ACT2.C b/16/keen456/KEEN4-6/KEEN6/K6_ACT2.C
new file mode 100755
index 00000000..ddea36fb
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN6/K6_ACT2.C
@@ -0,0 +1,1311 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+/*
+K6_ACT2.C
+=========
+
+Contains the following actor types (in this order):
+
+- Nospike
+- Gik
+- Turrets
+- Orbatrix
+- Bip & Bipship
+- Flect
+
+*/
+
+#include "CK_DEF.H"
+
+/*
+=============================================================================
+
+						  NOSPIKE
+
+temp1 = step counter for running on thin air
+temp2 = low byte: running flag; high byte: flash countdown
+temp3 = sprite pointer for the question mark
+temp4 = health
+
+=============================================================================
+*/
+
+statetype s_nospikestand     = {NOSPIKESTANDSPR,   NOSPIKESTANDSPR,   step,  false, true,  90,   0, 0, NULL, C_Nospike, R_Walk, &s_nospikewalk1};
+statetype s_nospikewalk1     = {NOSPIKEWALKL1SPR,  NOSPIKEWALKR1SPR,  step,  false, true,  10, 128, 0, T_NospikeWalk, C_Nospike, R_Walk, &s_nospikewalk2};
+statetype s_nospikewalk2     = {NOSPIKEWALKL2SPR,  NOSPIKEWALKR2SPR,  step,  false, true,  10, 128, 0, T_NospikeWalk, C_Nospike, R_Walk, &s_nospikewalk3};
+statetype s_nospikewalk3     = {NOSPIKEWALKL3SPR,  NOSPIKEWALKR3SPR,  step,  false, true,  10, 128, 0, T_NospikeWalk, C_Nospike, R_Walk, &s_nospikewalk4};
+statetype s_nospikewalk4     = {NOSPIKEWALKL4SPR,  NOSPIKEWALKR4SPR,  step,  false, true,  10, 128, 0, T_NospikeWalk, C_Nospike, R_Walk, &s_nospikewalk1};
+statetype s_nospikerun1      = {NOSPIKERUNL1SPR,   NOSPIKERUNR1SPR,   step,  false, true,   4, 128, 0, T_NospikeRun, C_Nospike, R_NospikeRun, &s_nospikerun2};
+statetype s_nospikerun2      = {NOSPIKERUNL2SPR,   NOSPIKERUNR2SPR,   step,  false, true,   4, 128, 0, T_NospikeRun, C_Nospike, R_NospikeRun, &s_nospikerun3};
+statetype s_nospikerun3      = {NOSPIKERUNL3SPR,   NOSPIKERUNR3SPR,   step,  false, true,   4, 128, 0, T_NospikeRun, C_Nospike, R_NospikeRun, &s_nospikerun4};
+statetype s_nospikerun4      = {NOSPIKERUNL4SPR,   NOSPIKERUNR4SPR,   step,  false, true,   4, 128, 0, T_NospikeRun, C_Nospike, R_NospikeRun, &s_nospikerun1};
+statetype s_nospikeconfused1 = {NOSPIKESTANDSPR,   NOSPIKESTANDSPR,   step,  false, false, 20,   0, 1, NULL, NULL, R_Draw, &s_nospikeconfused2};
+statetype s_nospikeconfused2 = {NOSPIKESTANDSPR,   NOSPIKESTANDSPR,   step,  false, false, 90,   0, 0, T_NospikeConfused, NULL, R_NospikeConfused, &s_nospikeconfused3};
+statetype s_nospikeconfused3 = {NOSPIKESTANDSPR,   NOSPIKESTANDSPR,   step,  false, false, 20,   0, 0, NULL, NULL, R_Draw, &s_nospikefall};
+statetype s_nospikefall      = {NOSPIKESTANDSPR,   NOSPIKESTANDSPR,   think, false, false,  0,   0, 0, T_Projectile, NULL, R_NospikeFall, NULL};
+statetype s_nospikestun      = {NOSPIKESTUNSPR,    NOSPIKESTUNSPR,    think, false, false,  0,   0, 0, T_Projectile, NULL, R_Stunned, &s_nospikestun};
+
+/*
+===========================
+=
+= SpawnNospike
+=
+===========================
+*/
+
+void SpawnNospike(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = nospikeobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -24*PIXGLOBAL;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	NewState(new, &s_nospikestand);
+	new->temp4 = 4;	// health
+}
+
+/*
+===========================
+=
+= T_NospikeWalk
+=
+===========================
+*/
+
+void T_NospikeWalk(objtype *ob)
+{
+	if (US_RndT() < 0x10)
+	{
+		ob->state = &s_nospikestand;
+	}
+	else if (ob->bottom == player->bottom && US_RndT() <= 0x20)
+	{
+		//
+		// start running towards player
+		//
+		if (player->x > ob->x)
+		{
+			ob->xdir = 1;
+		}
+		else
+		{
+			ob->xdir = -1;
+		}
+		ob->temp1 = 0;	// nospike is still on solid ground (should already be 0 anyway)
+		ob->temp2 = 1;	// nospike is running
+		if (ob->state == &s_nospikewalk1)
+		{
+			ob->state = &s_nospikerun2;
+		}
+		else if (ob->state == &s_nospikewalk2)
+		{
+			ob->state = &s_nospikerun3;
+		}
+		else if (ob->state == &s_nospikewalk3)
+		{
+			ob->state = &s_nospikerun4;
+		}
+		else if (ob->state == &s_nospikewalk4)
+		{
+			ob->state = &s_nospikerun1;
+		}
+	}
+}
+
+/*
+===========================
+=
+= T_NospikeRun
+=
+===========================
+*/
+
+void T_NospikeRun(objtype *ob)
+{
+	if (ob->temp1)
+		return;	// nospike is running on thin air, so we'd better not stop
+
+	if ( ( ( player->bottom != ob->bottom	// not on same ground level as Keen?
+			 || (ob->xdir == -1 && ob->x < player->x)
+			 || (ob->xdir == 1 && ob->x > player->x) ) // already ran past Keen?
+		  && US_RndT() < 8 )
+		|| !OnScreen(ob) )	// always stop running when off-screen
+	{
+		//
+		// stop running
+		//
+		ob->temp2 = 0;
+		if (ob->state == &s_nospikerun1)
+		{
+			ob->state = &s_nospikewalk2;
+		}
+		else if (ob->state == &s_nospikerun2)
+		{
+			ob->state = &s_nospikewalk3;
+		}
+		else if (ob->state == &s_nospikerun3)
+		{
+			ob->state = &s_nospikewalk4;
+		}
+		else if (ob->state == &s_nospikerun4)
+		{
+			ob->state = &s_nospikewalk1;
+		}
+	}
+}
+
+/*
+===========================
+=
+= C_Nospike
+=
+===========================
+*/
+
+void C_Nospike(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+	else if (hit->obclass == stunshotobj)
+	{
+		if (--ob->temp4 == 0)	// handle health
+		{
+			StunObj(ob, hit, &s_nospikestun);
+			ob->yspeed = -24;
+		}
+		else
+		{
+			if (player->x > ob->x)
+			{
+				ob->xdir = 1;
+			}
+			else
+			{
+				ob->xdir = -1;
+			}
+			ob->temp2 |= 0x400;	// draw white 4 times
+			ob->needtoreact = true;
+			if (ob->state == &s_nospikestand || ob->state == &s_nospikewalk1)
+			{
+				ChangeState(ob, &s_nospikerun2);
+			}
+			else if (ob->state == &s_nospikewalk2)
+			{
+				ChangeState(ob, &s_nospikerun3);
+			}
+			else if (ob->state == &s_nospikewalk3)
+			{
+				ChangeState(ob, &s_nospikerun4);
+			}
+			else if (ob->state == &s_nospikewalk4)
+			{
+				ChangeState(ob, &s_nospikerun1);
+			}
+			ExplodeShot(hit);
+		}
+	}
+	else if (hit->obclass == nospikeobj
+		&& (hit->temp2 & 0xFF) && (ob->temp2 & 0xFF)	// both nospikes are running?
+		&& hit->xdir != ob->xdir)	// running in opposite directions?
+	{
+		//
+		// stun both nospikes
+		//
+		ob->temp1=ob->temp2=ob->temp3=hit->temp1=hit->temp2=hit->temp3 = 0;
+		ob->temp4 = hit->temp4 = ob->obclass;
+		ChangeState(ob, &s_nospikestun);
+		ChangeState(hit, &s_nospikestun);
+		SD_PlaySound(SND_SMASH);
+		ob->obclass = hit->obclass = stunnedobj;
+		ob->yspeed = hit->yspeed = -24;
+	}
+}
+
+/*
+===========================
+=
+= T_NospikeConfused
+=
+===========================
+*/
+
+void T_NospikeConfused(objtype* ob)
+{
+	RF_RemoveSprite((void**)&ob->temp3);
+}
+
+/*
+===========================
+=
+= R_NospikeConfused
+=
+===========================
+*/
+
+void R_NospikeConfused(objtype *ob)
+{
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+	RF_PlaceSprite((void**)&ob->temp3, ob->x+TILEGLOBAL, ob->y-8*PIXGLOBAL, QUESTIONMARKSPR, spritedraw, 3);
+}
+
+/*
+===========================
+=
+= R_NospikeFall
+=
+===========================
+*/
+
+void R_NospikeFall(objtype *ob)
+{
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+	if (ob->hitnorth)
+	{
+		ob->temp1=ob->temp2=ob->temp3 = 0;
+		ob->temp4 = ob->obclass;
+		ChangeState(ob, &s_nospikestun);
+		SD_PlaySound(SND_SMASH);
+		ob->obclass = stunnedobj;
+		ob->yspeed = -24;
+	}
+}
+
+/*
+===========================
+=
+= R_NospikeRun
+=
+===========================
+*/
+
+void R_NospikeRun(objtype *ob)
+{
+	if (ob->hitnorth)
+	{
+		ob->temp1 = 0;	// on solid ground
+		if (ob->hiteast || ob->hitwest)
+		{
+			ob->x -= ob->xdir << 7;
+			NewState(ob, &s_nospikestand);
+			RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+			ob->temp2 = 0;	// no longer running or flashing white
+			return;
+		}
+	}
+	else
+	{
+		if (++ob->temp1 == 6)	// not on solid ground for 6 steps?
+		{
+			ChangeState(ob, &s_nospikeconfused1);
+#if 0
+			// bugfix:
+			ob->nothink = 0;	// to make sure T_NospikeConfused can remove the question mark sprite
+#endif
+		}
+	}
+	if (ob->temp2 & 0xFF00)
+	{
+		ob->temp2 -= 0x100;
+		RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, maskdraw, ob->priority);
+	}
+	else
+	{
+		RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+	}
+}
+
+/*
+=============================================================================
+
+						  GIK
+
+=============================================================================
+*/
+
+statetype s_gikwalk1      = {GIKWALKL1SPR,  GIKWALKR1SPR,  step,      false, true,  10, 128, 0, T_GikWalk, C_ClipTop, R_Walk, &s_gikwalk2};
+statetype s_gikwalk2      = {GIKWALKL2SPR,  GIKWALKR2SPR,  step,      false, true,  10, 128, 0, T_GikWalk, C_ClipTop, R_Walk, &s_gikwalk3};
+statetype s_gikwalk3      = {GIKWALKL3SPR,  GIKWALKR3SPR,  step,      false, true,  10, 128, 0, T_GikWalk, C_ClipTop, R_Walk, &s_gikwalk1};
+statetype s_gikjump       = {GIKJUMPLSPR,   GIKJUMPRSPR,   think,     false, false,  0,   0, 0, T_Projectile, C_ClipSide, R_GikJump, &s_gikslide1};
+statetype s_gikslide1     = {GIKSLIDEL1SPR, GIKSLIDER1SPR, stepthink, false, false,  6,   0, 0, T_GikSlide, C_Lethal, R_GikSlide, &s_gikslide2};
+statetype s_gikslide2     = {GIKSLIDEL2SPR, GIKSLIDER2SPR, stepthink, false, false,  6,   0, 0, T_GikSlide, C_Lethal, R_GikSlide, &s_gikslide1};
+statetype s_gikstand      = {GIKSLIDEL1SPR, GIKSLIDER1SPR, step,      false, true,  20,   0, 0, NULL, C_Lethal, R_Walk, &s_gikwalk1};
+
+/*
+===========================
+=
+= SpawnGik
+=
+===========================
+*/
+
+void SpawnGik(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = gikobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY);
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	NewState(new, &s_gikwalk1);
+}
+
+/*
+===========================
+=
+= T_GikWalk
+=
+===========================
+*/
+
+void T_GikWalk(objtype *ob)
+{
+	Sint16 xdist;
+
+	if (ob->hitnorth != 9)	// if NOT on flat ground that kills Keen
+	{
+		xdist = player->x - ob->x;
+		if (player->bottom <= ob->bottom && ob->bottom - player->bottom <= 4*TILEGLOBAL)
+		{
+			if (xdist < 0)
+			{
+				ob->xdir = -1;
+			}
+			else
+			{
+				ob->xdir = 1;
+			}
+			if (xdist >= -7*TILEGLOBAL && xdist <= 7*TILEGLOBAL
+				&& (xdist <= -TILEGLOBAL || xdist >= TILEGLOBAL) )
+			{
+				if (xdist < 0)
+				{
+					ob->xspeed = -40;
+				}
+				else
+				{
+					ob->xspeed = 40;
+				}
+				ob->yspeed = -28;
+				ob->state = &s_gikjump;
+				SD_PlaySound(SND_GIKJUMP);
+			}
+		}
+	}
+}
+
+/*
+===========================
+=
+= T_GikSlide
+=
+===========================
+*/
+
+void T_GikSlide(objtype *ob)
+{
+	// tic masks for friction, based on slope type and direction
+	// 0 - no friction
+	// 7 - lowest friction (speed decreases every 8 tics)
+	// 3 - medium friction (speed decreases every 4 tics)
+	// 1 - highest friction (speed decreases every 2 tics)
+	static Sint16 rticmask[8] = {0, 7, 0, 0, 0, 3, 3, 1};
+	static Sint16 lticmask[8] = {0, 7, 3, 3, 1, 0, 0, 0};
+
+	Sint16 ticmask;
+	Sint16 slope;
+	Sint32 i;
+
+	DoGravity(ob);
+
+	slope = ob->hitnorth & 7;
+	if (ob->xdir == 1)
+	{
+		ticmask = rticmask[slope];
+	}
+	else
+	{
+		ticmask = lticmask[slope];
+	}
+
+	if (ob->xspeed == 0 && ob->hitnorth)
+	{
+		ob->state = &s_gikstand;
+	}
+	else
+	{
+		for (i = lasttimecount-tics; i < lasttimecount; i++)
+		{
+			if (ticmask && !(i & ticmask))
+			{
+				if ((ob->xspeed < 0 && ++ob->xspeed == 0)
+					|| (ob-> xspeed > 0 && --ob->xspeed == 0))
+				{
+					ob->state = &s_gikstand;
+					return;
+				}
+			}
+			xtry += ob->xspeed;
+		}
+	}
+}
+
+/*
+===========================
+=
+= R_GikJump
+=
+===========================
+*/
+
+void R_GikJump(objtype *ob)
+{
+	if (ob->hiteast || ob->hitwest)
+		ob->xspeed = 0;
+
+	if (ob->hitsouth)
+		ob->yspeed = 0;
+
+	if (ob->hitnorth)
+	{
+		ob->yspeed = 0;
+		SD_PlaySound(SND_GIKLAND);
+		ChangeState(ob, ob->state->nextstate);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+===========================
+=
+= R_GikSlide
+=
+===========================
+*/
+
+void R_GikSlide(objtype *ob)
+{
+	if ((ob->hiteast && ob->xspeed < 0) || (ob->hitwest && ob->xspeed > 0))
+		ob->xspeed = 0;
+
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+=============================================================================
+
+						  CANNON
+
+temp1 = direction
+
+=============================================================================
+*/
+
+statetype s_cannon     = {0,            0,            step,      false, false, 120, 0, 0, NULL, NULL, R_Draw, &s_cannonfire};
+statetype s_cannonfire = {0,            0,            step,      true,  false,   1, 0, 0, T_Cannon, NULL, R_Draw, &s_cannon};
+statetype s_cshot1     = {LASER1SPR,    LASER1SPR,    stepthink, false, false,   8, 0, 0, T_Velocity, C_CShot, R_CShot, &s_cshot2};
+statetype s_cshot2     = {LASER2SPR,    LASER2SPR,    stepthink, false, false,   8, 0, 0, T_Velocity, C_CShot, R_CShot, &s_cshot3};
+statetype s_cshot3     = {LASER3SPR,    LASER3SPR,    stepthink, false, false,   8, 0, 0, T_Velocity, C_CShot, R_CShot, &s_cshot4};
+statetype s_cshot4     = {LASER4SPR,    LASER4SPR,    stepthink, false, false,   8, 0, 0, T_Velocity, C_CShot, R_CShot, &s_cshot1};
+statetype s_cshothit1  = {LASERHIT1SPR, LASERHIT1SPR, step,      false, false,  10, 0, 0, NULL, NULL, R_Draw, &s_cshothit2};
+statetype s_cshothit2  = {LASERHIT2SPR, LASERHIT2SPR, step,      false, false,  10, 0, 0, NULL, NULL, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnCannon
+=
+===========================
+*/
+
+void SpawnCannon(Uint16 tileX, Uint16 tileY, Sint16 dir)
+{
+	GetNewObj(false);
+	new->obclass = cannonobj;
+	new->active = ac_yes;
+	new->tileright = new->tileleft = tileX;
+	new->tiletop = new->tilebottom = tileY;
+	new->x = new->left = new->right = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = new->top = new->bottom = CONVERT_TILE_TO_GLOBAL(tileY);
+	new->temp1 = dir;
+	NewState(new, &s_cannon);
+}
+
+/*
+===========================
+=
+= T_Cannon
+=
+===========================
+*/
+
+void T_Cannon(objtype *ob)
+{
+	GetNewObj(true);
+	new->obclass = mshotobj;
+	new->active = ac_yes;	// BUG? NOT removable in Keen 6 (checked v1.0, v1.4 and v1.5)
+	new->x = ob->x;
+	new->y = ob->y;
+	switch (ob->temp1)
+	{
+	case 0:
+		new->yspeed = -64;
+		break;
+	case 1:
+		new->xspeed = 64;
+		break;
+	case 2:
+		new->yspeed = 64;
+		break;
+	case 3:
+		new->xspeed = -64;
+	}
+	NewState(new, &s_cshot1);
+	SD_PlaySound(SND_ENEMYSHOT);
+}
+
+/*
+===========================
+=
+= C_CShot
+=
+===========================
+*/
+
+void C_CShot(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+		ChangeState(ob, &s_cshothit1);
+	}
+}
+
+/*
+===========================
+=
+= R_CShot
+=
+===========================
+*/
+
+void R_CShot(objtype *ob)
+{
+	if (ob->hitnorth || ob->hiteast || ob->hitsouth || ob->hitwest)
+	{
+		SD_PlaySound(SND_ENEMYSHOTEXPLODE);
+		ChangeState(ob, &s_cshothit1);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+=============================================================================
+
+						  ORBATRIX
+
+temp1 = bounce counter
+temp2 = amount to move up during uncurl animation
+temp3 = float offset
+temp4 = float direction (up or down)
+
+=============================================================================
+*/
+
+statetype s_orbatrix1       = {ORBATRIXL1SPR,    ORBATRIXR1SPR,    slide,     false, true,  12, 16, 0, T_OrbatrixFly, C_Orbatrix, R_Orbatrix, &s_orbatrix2};
+statetype s_orbatrix2       = {ORBATRIXL2SPR,    ORBATRIXR2SPR,    slide,     false, true,  12, 16, 0, T_OrbatrixFly, C_Orbatrix, R_Orbatrix, &s_orbatrix1};
+statetype s_orbatrixcurl1   = {ORBATRIX1SPR,     ORBATRIX1SPR,     stepthink, false, true,  12,  0, 0, NULL, C_Orbatrix, R_Orbatrix, &s_orbatrixcurl2};
+statetype s_orbatrixcurl2   = {ORBATRIXCURLSPR,  ORBATRIXCURLSPR,  stepthink, false, true,  12,  0, 0, NULL, C_Orbatrix, R_Orbatrix, &s_orbatrixcurl3};
+statetype s_orbatrixcurl3   = {ORBATRIXCURLSPR,  ORBATRIXCURLSPR,  think,     false, true,  12,  0, 0, T_OrbatrixCurl, C_Orbatrix, R_Orbatrix, &s_orbatrixbounce1};
+statetype s_orbatrixuncurl1 = {ORBATRIXSPIN1SPR, ORBATRIXSPIN1SPR, think,     false, false, 12,  0, 0, T_OrbatrixUncurl, C_OrbatrixBounce, R_Draw, &s_orbatrixuncurl2};
+statetype s_orbatrixuncurl2 = {ORBATRIXCURLSPR,  ORBATRIXCURLSPR,  step,      false, false, 12,  0, 0, NULL, C_OrbatrixBounce, R_Draw, &s_orbatrixidle1};
+statetype s_orbatrixidle1   = {ORBATRIX1SPR,     ORBATRIX1SPR,     stepthink, false, true,  12,  0, 0, NULL, C_Orbatrix, R_Orbatrix, &s_orbatrixidle2};
+statetype s_orbatrixidle2   = {ORBATRIX2SPR,     ORBATRIX2SPR,     stepthink, false, true,  12,  0, 0, NULL, C_Orbatrix, R_Orbatrix, &s_orbatrixidle3};
+statetype s_orbatrixidle3   = {ORBATRIX3SPR,     ORBATRIX3SPR,     stepthink, false, true,  12,  0, 0, NULL, C_Orbatrix, R_Orbatrix, &s_orbatrixidle4};
+statetype s_orbatrixidle4   = {ORBATRIX4SPR,     ORBATRIX4SPR,     stepthink, false, true,  12,  0, 0, NULL, C_Orbatrix, R_Orbatrix, &s_orbatrix1};
+statetype s_orbatrixbounce1 = {ORBATRIXSPIN4SPR, ORBATRIXSPIN1SPR, stepthink, false, false,  6,  0, 0, T_Projectile, C_OrbatrixBounce, R_OrbatrixBounce, &s_orbatrixbounce2};
+statetype s_orbatrixbounce2 = {ORBATRIXSPIN3SPR, ORBATRIXSPIN2SPR, stepthink, false, false,  6,  0, 0, T_Projectile, C_OrbatrixBounce, R_OrbatrixBounce, &s_orbatrixbounce3};
+statetype s_orbatrixbounce3 = {ORBATRIXSPIN2SPR, ORBATRIXSPIN3SPR, stepthink, false, false,  6,  0, 0, T_Projectile, C_OrbatrixBounce, R_OrbatrixBounce, &s_orbatrixbounce4};
+statetype s_orbatrixbounce4 = {ORBATRIXSPIN1SPR, ORBATRIXSPIN4SPR, stepthink, false, false,  6,  0, 0, T_Projectile, C_OrbatrixBounce, R_OrbatrixBounce, &s_orbatrixbounce1};
+
+/*
+===========================
+=
+= SpawnOrbatrix
+=
+===========================
+*/
+
+void SpawnOrbatrix(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = orbatrixobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -24*PIXGLOBAL;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	new->temp4 = 1;
+	NewState(new, &s_orbatrix1);
+}
+
+/*
+===========================
+=
+= T_OrbatrixFly
+=
+===========================
+*/
+
+void T_OrbatrixFly(objtype *ob)
+{
+	Sint16 dist;
+
+	if (US_RndT() < 0x20)
+	{
+		ob->state = &s_orbatrixidle1;
+		return;
+	}
+
+	if (ob->bottom != player->bottom)
+	{
+		return;
+	}
+
+	dist = player->x - ob->x;
+	ob->xdir = (dist < 0)? -1 : 1;
+	if (dist > -5*TILEGLOBAL && dist < 5*TILEGLOBAL)
+	{
+		ob->state = &s_orbatrixcurl1;
+	}
+}
+
+/*
+===========================
+=
+= C_Orbatrix
+=
+===========================
+*/
+
+void C_Orbatrix(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == stunshotobj)
+	{
+		ExplodeShot(hit);
+		ChangeState(ob, &s_orbatrixidle1);
+	}
+}
+
+/*
+===========================
+=
+= R_Orbatrix
+=
+===========================
+*/
+
+void R_Orbatrix(objtype *ob)
+{
+	//
+	// ugly hack: apply float offset before drawing the sprite
+	// (it's ugly because the sprite moves up/down, but the hitbox doesn't)
+	//
+	ob->y -= ob->temp3;
+	R_Walk(ob);
+	ob->y += ob->temp3;
+
+	//
+	// update the float offset
+	//
+	ob->temp3 = ob->temp3 + ob->temp4 * tics * 4;
+	if (ob->temp3 > 8*PIXGLOBAL)
+	{
+		ob->temp3 = 8*PIXGLOBAL;
+		ob->temp4 = -1;
+	}
+	else if (ob->temp3 < -8*PIXGLOBAL)
+	{
+		ob->temp3 = -8*PIXGLOBAL;
+		ob->temp4 = 1;
+	}
+}
+
+/*
+===========================
+=
+= R_OrbatrixBounce
+=
+===========================
+*/
+
+void R_OrbatrixBounce(objtype *ob)
+{
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+
+	if (ob->hitnorth)
+	{
+		ob->yspeed = -ob->yspeed;
+	}
+	if (ob->hitnorth || ob->hitwest || ob->hiteast)
+	{
+		ob->xspeed = -ob->xspeed;
+		SD_PlaySound(SND_ORBATRIXBOUNCE);
+		if (ob->hitnorth && --ob->temp1 == 0)
+		{
+			ChangeState(ob, &s_orbatrixuncurl1);
+			ob->temp2 = 24*PIXGLOBAL;
+		}
+	}
+}
+
+/*
+===========================
+=
+= T_OrbatrixCurl
+=
+===========================
+*/
+
+void T_OrbatrixCurl(objtype *ob)
+{
+	if (ob->temp3 >= 16)
+	{
+		ob->xspeed = ob->xdir * 60;
+		ob->yspeed = -32;
+		ob->y -= ob->temp3;
+		ob->temp1 = 5;	// bounce 5 times
+		ob->state = ob->state->nextstate;
+	}
+	ob->needtoreact = true;
+}
+
+/*
+===========================
+=
+= T_OrbatrixUncurl
+=
+===========================
+*/
+
+void T_OrbatrixUncurl(objtype *ob)
+{
+	ob->temp2 += (ytry = tics * -8);
+	if (ob->temp2 <= 0)
+	{
+		ytry -= ob->temp2;
+		ob->state = ob->state->nextstate;
+	}
+}
+
+/*
+===========================
+=
+= C_OrbatrixBounce
+=
+===========================
+*/
+
+void C_OrbatrixBounce(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+	else if (hit->obclass == stunshotobj)
+	{
+		ExplodeShot(hit);
+		ob->xspeed = 0;
+	}
+}
+
+/*
+=============================================================================
+
+						  BIP
+
+=============================================================================
+*/
+
+statetype s_bipstand      = {BIPSTANDSPR,    BIPSTANDSPR,    step,  false, true, 30,  0, 0, NULL, C_Bip, R_Walk, &s_bipwalk1};
+statetype s_bipwalk1      = {BIPWALKL1SPR,   BIPWALKR1SPR,   step,  true,  true,  4, 32, 0, T_BipWalk, C_Bip, R_Walk, &s_bipwalk2};
+statetype s_bipwalk2      = {BIPWALKL2SPR,   BIPWALKR2SPR,   step,  true,  true,  4, 32, 0, T_BipWalk, C_Bip, R_Walk, &s_bipwalk3};
+statetype s_bipwalk3      = {BIPWALKL3SPR,   BIPWALKR3SPR,   step,  true,  true,  4, 32, 0, T_BipWalk, C_Bip, R_Walk, &s_bipwalk4};
+statetype s_bipwalk4      = {BIPWALKL4SPR,   BIPWALKR4SPR,   step,  true,  true,  4, 32, 0, T_BipWalk, C_Bip, R_Walk, &s_bipwalk1};
+statetype s_bipsquished   = {BIPSQUISHEDSPR, BIPSQUISHEDSPR, think, false, true,  0,  0, 0, T_Projectile, NULL, R_Draw, NULL};
+
+/*
+===========================
+=
+= T_BipWalk
+=
+===========================
+*/
+
+void T_BipWalk(objtype *ob)
+{
+	if (ob->bottom == player->bottom)
+	{
+		if (ob->right < player->left - 4*PIXGLOBAL)
+			ob->xdir = 1;
+
+		if (ob->left > player->right + 4*PIXGLOBAL)
+			ob->xdir = -1;
+	}
+	else if (US_RndT() < 0x10)
+	{
+		ob->xdir = -ob->xdir;
+		ob->state = &s_bipstand;
+	}
+}
+
+/*
+===========================
+=
+= C_Bip
+=
+===========================
+*/
+
+void C_Bip(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj && hit->ymove > 0)
+	{
+		SD_PlaySound(SND_BIPSQUISH);
+		ob->obclass = inertobj;
+		ChangeState(ob, &s_bipsquished);
+	}
+}
+
+/*
+=============================================================================
+
+						  BIPSHIP
+
+=============================================================================
+*/
+
+statetype s_bipship         = {BIPSHIPLSPR,        BIPSHIPRSPR,        think,     false, true,      0, 0, 0, T_BipshipFly, C_Bipship, R_Draw, &s_bipship};
+statetype s_bipshipshot     = {BIPSHIPSHOTSPR,     BIPSHIPSHOTSPR,     think,     false, false,     0, 0, 0, T_Velocity, C_Lethal, R_BipShot, NULL};
+statetype s_bipshipturn1    = {BIPSHIPRTURN1SPR,   BIPSHIPLTURN1SPR,   stepthink, false, true,     10, 0, 0, T_BipshipTurn, C_Bipship, R_Draw, &s_bipshipturn2};
+statetype s_bipshipturn2    = {BIPSHIPRTURN2SPR,   BIPSHIPLTURN2SPR,   stepthink, false, true,     10, 0, 0, T_BipshipTurn, C_Bipship, R_Draw, &s_bipshipturn3};
+statetype s_bipshipturn3    = {BIPSHIPRTURN3SPR,   BIPSHIPLTURN3SPR,   stepthink, false, true,     10, 0, 0, T_BipshipTurn, C_Bipship, R_Draw, &s_bipshipturn4};
+statetype s_bipshipturn4    = {BIPSHIPRTURN4SPR,   BIPSHIPLTURN4SPR,   stepthink, false, true,     10, 0, 0, T_BipshipTurn, C_Bipship, R_Draw, &s_bipship};
+statetype s_bipshipexplode1 = {BIPSHIPEXPLODE2SPR, BIPSHIPEXPLODE1SPR, think,     false, false,     0, 0, 0, T_Projectile, NULL, R_Land, &s_bipshipexplode2};
+statetype s_bipshipexplode2 = {BIPSHIPEXPLODE2SPR, BIPSHIPEXPLODE1SPR, step,      true,  false,     1, 0, 0, T_BipshipExplode, NULL, R_Land, &s_bipshipexplode3};
+statetype s_bipshipexplode3 = {BIPSHIPEXPLODE5SPR, BIPSHIPEXPLODE5SPR, step,      true,  false, 30000, 0, 0, NULL, NULL, R_Land, &s_bipshipexplode3};
+statetype s_bipshipsmoke1   = {BIPSHIPEXPLODE3SPR, BIPSHIPEXPLODE3SPR, step,      true,  false,    10, 0, 0, NULL, NULL, R_Draw, &s_bipshipsmoke2};
+statetype s_bipshipsmoke2   = {BIPSHIPEXPLODE4SPR, BIPSHIPEXPLODE4SPR, step,      true,  false,    10, 0, 0, NULL, NULL, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnBipship
+=
+===========================
+*/
+
+void SpawnBipship(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = bipshipobj;
+	new->active = ac_yes;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY)+ -24*PIXGLOBAL;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->xspeed = new->xdir * 20;
+	NewState(new, &s_bipship);
+}
+
+/*
+===========================
+=
+= R_BipShot
+=
+===========================
+*/
+
+void R_BipShot(objtype *ob)
+{
+	if (ob->hitnorth || ob->hitsouth || ob->hiteast || ob->hitwest)
+	{
+		RemoveObj(ob);
+	}
+	else
+	{
+		RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+	}
+}
+
+/*
+===========================
+=
+= T_BipshipTurn
+=
+===========================
+*/
+
+void T_BipshipTurn(objtype *ob)
+{
+	AccelerateX(ob, ob->xdir, 20);
+}
+
+/*
+===========================
+=
+= T_BipshipFly
+=
+===========================
+*/
+
+void T_BipshipFly(objtype *ob)
+{
+	Uint16 far *map;
+	Sint16 dir;
+	Uint16 tile, tx, ty;
+
+	AccelerateX(ob, ob->xdir, 20);
+	dir = ob->xdir;
+	if (player->bottom + TILEGLOBAL - ob->bottom <= 2*TILEGLOBAL)
+	{
+		if (player->x < ob->x)
+		{
+			dir = -1;
+		}
+		else
+		{
+			dir = 1;
+		}
+		if (ob->xdir == dir && US_RndT() < tics*4)
+		{
+			SD_PlaySound(SND_KEENFIRE);
+			GetNewObj(true);
+			new->obclass = mshotobj;
+			new->active = ac_removable;
+			new->priority = 1;
+			if (ob->xdir == 1)
+			{
+				new->x = ob->x + TILEGLOBAL;
+				new->xspeed = 64;
+			}
+			else
+			{
+				new->x = ob->x;
+				new->xspeed = -64;
+			}
+			new->y = ob->y + 10*PIXGLOBAL;
+			new->yspeed = 16;
+			NewState(new, &s_bipshipshot);
+		}
+	}
+
+	tx = ob->tilemidx + dir*4;
+	map = mapsegs[1] + mapbwidthtable[ob->tiletop]/2 + tx;
+
+	for (ty = ob->tiletop; ty <= ob->tilebottom; ty++, map += mapwidth)
+	{
+		tile = *map;
+		if (tinf[tile+EASTWALL] || tinf[tile+WESTWALL])
+		{
+			dir = -dir;
+			goto check_turn;
+		}
+	}
+	tile = *map;
+	if (!tinf[tile+NORTHWALL])
+	{
+		dir = -dir;
+	}
+check_turn:
+	if (dir != ob->xdir)
+	{
+		ob->xdir = dir;
+		ChangeState(ob, &s_bipshipturn1);
+	}
+}
+
+/*
+===========================
+=
+= T_BipshipExplode
+=
+===========================
+*/
+
+void T_BipshipExplode(objtype *ob)
+{
+	SD_PlaySound(SND_BIPSHIPEXPLODE);
+
+	GetNewObj(true);
+	new->obclass = inertobj;
+	new->active = ac_yes;
+	new->priority = 2;
+	new->x = ob->x;
+	new->y = ob->y - 24*PIXGLOBAL;
+	NewState(new, &s_bipshipsmoke1);
+
+	GetNewObj(true);
+	new->obclass = bipobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = ob->x;
+	new->y = ob->y - 8*PIXGLOBAL;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	NewState(new, &s_bipstand);
+}
+
+/*
+===========================
+=
+= C_Bipship
+=
+===========================
+*/
+
+void C_Bipship(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == stunshotobj)
+	{
+		ExplodeShot(hit);
+		ChangeState(ob, &s_bipshipexplode1);
+	}
+}
+
+/*
+=============================================================================
+
+						  FLECT
+
+=============================================================================
+*/
+
+statetype s_flectstand = {FLECTSTANDLSPR, FLECTSTANDRSPR, think, false, true, 60,   0, 0, T_FlectStand, C_Flect, R_Flect, &s_flectwalk1};
+statetype s_flectturn  = {FLECTSTANDSPR,  FLECTSTANDSPR,  step,  false, true,  8,   0, 0, NULL, C_Flect, R_Flect, &s_flectwalk1};
+statetype s_flectwalk1 = {FLECTWALKL1SPR, FLECTWALKR1SPR, step,  false, true, 10, 128, 0, T_FlectWalk, C_Flect, R_Flect, &s_flectwalk2};
+statetype s_flectwalk2 = {FLECTWALKL2SPR, FLECTWALKR2SPR, step,  false, true, 10, 128, 0, T_FlectWalk, C_Flect, R_Flect, &s_flectwalk3};
+statetype s_flectwalk3 = {FLECTWALKL3SPR, FLECTWALKR3SPR, step,  false, true, 10, 128, 0, T_FlectWalk, C_Flect, R_Flect, &s_flectwalk4};
+statetype s_flectwalk4 = {FLECTWALKL4SPR, FLECTWALKR4SPR, step,  false, true, 10, 128, 0, T_FlectWalk, C_Flect, R_Flect, &s_flectwalk1};
+statetype s_flectstun  = {FLECTSTUNSPR,   FLECTSTUNSPR,   think, false, false, 0,   0, 0, T_Projectile, NULL, R_Stunned, &s_flectstun};
+
+/*
+===========================
+=
+= SpawnFlect
+=
+===========================
+*/
+
+void SpawnFlect(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = flectobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -1*TILEGLOBAL;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	NewState(new, &s_flectwalk1);
+}
+
+/*
+===========================
+=
+= T_FlectStand
+=
+===========================
+*/
+
+void T_FlectStand(objtype *ob)
+{
+	if (player->x < ob->x)
+	{
+		if (ob->xdir != -1)
+		{
+			ob->state = &s_flectturn;
+			ob->xdir = -1;
+		}
+		else
+		{
+			ob->state = &s_flectwalk1;
+		}
+	}
+	else
+	{
+		if (ob->xdir != 1)
+		{
+			ob->state = &s_flectturn;
+			ob->xdir = 1;
+		}
+		else
+		{
+			ob->state = &s_flectwalk1;
+		}
+	}
+}
+
+/*
+===========================
+=
+= T_FlectWalk
+=
+===========================
+*/
+
+void T_FlectWalk(objtype *ob)
+{
+	if (player->x < ob->x && ob->xdir == 1)
+	{
+		if (ob->xdir != -1)	// always true here!
+		{
+			ob->state = &s_flectturn;
+		}
+		ob->xdir = -1;
+	}
+
+	if (player->x > ob->x && ob->xdir == -1)
+	{
+		if (ob->xdir != 1)	// always true here!
+		{
+			ob->state = &s_flectturn;
+		}
+		ob->xdir = 1;
+	}
+
+	if (US_RndT() < 0x20)
+	{
+		ob->state = &s_flectstand;
+	}
+}
+
+/*
+===========================
+=
+= C_Flect
+=
+===========================
+*/
+
+void C_Flect(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		ClipToSpriteSide(hit, ob);
+	}
+	else if (hit->obclass == stunshotobj)
+	{
+		if (hit->xdir == 0)
+		{
+			StunObj(ob, hit, &s_flectstun);
+		}
+		else if (hit->xdir != ob->xdir)
+		{
+			// reflect shot:
+			hit->xdir = ob->xdir;
+			hit->temp4 = true;	// shot can now stun Keen
+			SD_PlaySound(SND_SHOTBOUNCE);
+		}
+	}
+}
+
+/*
+===========================
+=
+= R_Flect
+=
+===========================
+*/
+
+void R_Flect(objtype *ob)
+{
+	if (ob->xdir == 1 && ob->hitwest)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = -1;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	else if (ob->xdir == -1 && ob->hiteast)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = 1;
+		ob->nothink = US_RndT() >> 5;
+		ChangeState(ob, ob->state);
+	}
+	else if (!ob->hitnorth)
+	{
+		ob->x -= ob->xmove;
+		ob->xdir = -ob->xdir;
+		ChangeState(ob, ob->state);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
diff --git a/16/keen456/KEEN4-6/KEEN6/K6_ACT3.C b/16/keen456/KEEN4-6/KEEN6/K6_ACT3.C
new file mode 100755
index 00000000..81efc993
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN6/K6_ACT3.C
@@ -0,0 +1,765 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+/*
+K6_ACT3.C
+=========
+
+Contains the following actor types (in this order):
+
+- Fleex
+- Bobba
+- Babobba
+- Blorb
+- Ceilick
+
+*/
+
+#include "CK_DEF.H"
+
+/*
+=============================================================================
+
+						  FLEEX
+
+temp1 = flash countdown
+temp2 = health
+
+=============================================================================
+*/
+
+statetype s_fleexwalk1 = {FLEEXWALKL1SPR, FLEEXWALKR1SPR, step,  false, true,  7, 128, 0, T_FleexWalk, C_Fleex, R_Blooguard, &s_fleexwalk2};
+statetype s_fleexwalk2 = {FLEEXWALKL2SPR, FLEEXWALKR2SPR, step,  false, true,  7, 128, 0, T_FleexWalk, C_Fleex, R_Blooguard, &s_fleexwalk1};
+statetype s_fleexrun1  = {FLEEXWALKL1SPR, FLEEXWALKR1SPR, step,  false, true,  7, 128, 0, NULL, C_Fleex, R_Blooguard, &s_fleexrun2};
+statetype s_fleexrun2  = {FLEEXWALKL2SPR, FLEEXWALKR2SPR, step,  false, true,  7, 128, 0, NULL, C_Fleex, R_Blooguard, &s_fleexrun3};
+statetype s_fleexrun3  = {FLEEXWALKL1SPR, FLEEXWALKR1SPR, step,  false, true,  7, 128, 0, NULL, C_Fleex, R_Blooguard, &s_fleexrun4};
+statetype s_fleexrun4  = {FLEEXWALKL2SPR, FLEEXWALKR2SPR, step,  false, true,  7, 128, 0, NULL, C_Fleex, R_Blooguard, &s_fleexwalk1};
+statetype s_fleexlook1 = {FLEEXLOOK1SPR,  FLEEXLOOK1SPR,  step,  false, true, 60,   0, 0, NULL, C_Fleex, R_Blooguard, &s_fleexlook2};
+statetype s_fleexlook2 = {FLEEXLOOK2SPR,  FLEEXLOOK2SPR,  step,  false, true, 60,   0, 0, T_FleexLook, C_Fleex, R_Blooguard, &s_fleexrun1};
+statetype s_fleexstun  = {FLEEXSTUNSPR,   FLEEXSTUNSPR,   think, false, false, 0,   0, 0, T_Projectile, NULL, R_Stunned, NULL};
+
+/*
+===========================
+=
+= SpawnFleex
+=
+===========================
+*/
+
+void SpawnFleex(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = fleexobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -40*PIXGLOBAL;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	NewState(new, &s_fleexwalk1);
+	new->temp2 = 4;	// health
+}
+
+/*
+===========================
+=
+= T_FleexWalk
+=
+===========================
+*/
+
+void T_FleexWalk(objtype *ob)
+{
+	if (!player->xmove && !ob->temp1)
+	{
+		ob->state = &s_fleexlook1;
+	}
+	else
+	{
+		ob->xdir = (ob->x < player->x)? 1 : -1;
+	}
+}
+
+/*
+===========================
+=
+= T_FleexLook
+=
+===========================
+*/
+
+void T_FleexLook(objtype *ob)
+{
+	ob->xdir = (ob->x < player->x)? 1 : -1;
+}
+
+/*
+===========================
+=
+= C_Fleex
+=
+===========================
+*/
+
+void C_Fleex(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+	if (hit->obclass == stunshotobj)	// this is not 'else if' in the original code
+	{
+		if (--ob->temp2 == 0)
+		{
+			StunObj(ob, hit, &s_fleexstun);
+			ob->yspeed = -20;
+		}
+		else
+		{
+			ob->temp1 = 2;	// draw white twice
+			ob->needtoreact = true;
+			ExplodeShot(hit);
+			if (ob->state == &s_fleexlook1 || ob->state == &s_fleexlook2)
+			{
+				ob->xdir = (ob->x < player->x)? 1 : -1;
+				ChangeState(ob, &s_fleexwalk1);
+			}
+		}
+	}
+}
+
+/*
+=============================================================================
+
+						  BOBBA
+
+temp1 = jump counter
+
+=============================================================================
+*/
+
+statetype s_bobbajump1       = {BOBBAL2SPR,    BOBBAR2SPR,    stepthink, false, false,  8,  0, 0, T_Projectile, C_Bobba, R_Bobba, &s_bobbajump2};
+statetype s_bobbajump2       = {BOBBAL3SPR,    BOBBAR3SPR,    think,     false, false,  8,  0, 0, T_Projectile, C_Bobba, R_Bobba, &s_bobbajump2};
+statetype s_bobbastand       = {BOBBAL1SPR,    BOBBAR1SPR,    step,      false, false, 20,  0, 0, T_BobbaStand, C_Bobba, R_Draw, &s_bobbajump1};
+statetype s_bobbaattack      = {BOBBAL1SPR,    BOBBAR1SPR,    step,      false, false, 40,  0, 0, NULL, C_Bobba, R_Draw, &s_bobbajump1};
+statetype s_bobbashot1       = {BOBBASHOT1SPR, BOBBASHOT1SPR, step,      false, false,  8,  0, 0, NULL, NULL, R_Draw, &s_bobbashot2};
+statetype s_bobbashot2       = {BOBBASHOT2SPR, BOBBASHOT2SPR, step,      false, false,  8,  0, 0, NULL, NULL, R_Draw, &s_bobbashot3};
+statetype s_bobbashot3       = {BOBBASHOT1SPR, BOBBASHOT1SPR, step,      false, false,  8,  0, 0, NULL, NULL, R_Draw, &s_bobbashot4};
+statetype s_bobbashot4       = {BOBBASHOT2SPR, BOBBASHOT2SPR, step,      false, false,  8,  0, 0, T_BobbaShot, NULL, R_Draw, &s_bobbashot5};
+statetype s_bobbashot5       = {BOBBASHOT3SPR, BOBBASHOT3SPR, slide,     false, false,  8, 48, 0, NULL, C_Lethal, R_BobbaShot, &s_bobbashot6};
+statetype s_bobbashot6       = {BOBBASHOT4SPR, BOBBASHOT4SPR, slide,     false, false,  8, 48, 0, NULL, C_Lethal, R_BobbaShot, &s_bobbashot7};
+statetype s_bobbashot7       = {BOBBASHOT5SPR, BOBBASHOT5SPR, slide,     false, false,  8, 48, 0, NULL, C_Lethal, R_BobbaShot, &s_bobbashot8};
+statetype s_bobbashot8       = {BOBBASHOT6SPR, BOBBASHOT6SPR, slide,     false, false,  8, 48, 0, NULL, C_Lethal, R_BobbaShot, &s_bobbashot5};
+statetype s_bobbashotvanish1 = {BOBBASHOT6SPR, BOBBASHOT6SPR, step,      false, false,  8,  0, 0, NULL, NULL, R_Draw, &s_bobbashotvanish2};
+statetype s_bobbashotvanish2 = {BOBBASHOT6SPR, BOBBASHOT6SPR, step,      false, false,  8,  0, 0, NULL, NULL, R_Draw, &s_bobbashotvanish3};
+statetype s_bobbashotvanish3 = {BOBBASHOT6SPR, BOBBASHOT6SPR, step,      false, false,  8,  0, 0, NULL, NULL, R_Draw, NULL};
+
+/*
+===========================
+=
+= SpawnBobba
+=
+===========================
+*/
+
+void SpawnBobba(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = bobbaobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -2*TILEGLOBAL;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	NewState(new, &s_bobbajump1);
+}
+
+/*
+===========================
+=
+= T_BobbaShot
+=
+===========================
+*/
+
+#pragma argsused
+void T_BobbaShot(objtype *ob)
+{
+	SD_PlaySound(SND_BOBBASHOT);
+}
+
+/*
+===========================
+=
+= T_BobbaStand
+=
+===========================
+*/
+
+void T_BobbaStand(objtype *ob)
+{
+	Sint16 i;
+	Uint16 far *map;
+
+	if (++ob->temp1 == 3)
+	{
+		ob->temp1 = 0;
+		GetNewObj(true);
+		new->active = ac_removable;
+		new->obclass = mshotobj;
+		new->y = ob->y + 11*PIXGLOBAL;
+		new->xdir = ob->xdir;
+		if (ob->xdir == 1)
+		{
+			new->x = ob->x + 16*PIXGLOBAL;
+		}
+		else
+		{
+			new->x = ob->x + 11*PIXGLOBAL;
+		}
+		NewState(new, &s_bobbashot1);
+		new->priority = 2;
+		ob->state = &s_bobbaattack;
+	}
+	else
+	{
+		map = mapsegs[1] + mapbwidthtable[ob->tilebottom+1]/2 + ob->tilemidx;
+		for (i=0; i<4; map += ob->xdir, i++)
+		{
+			if ( !tinf[*map+NORTHWALL]
+				&& !tinf[*(map-mapwidth)+NORTHWALL]
+				&& !tinf[*(map+mapwidth)+NORTHWALL] )
+			{
+				ob->xdir = -ob->xdir;
+				break;
+			}
+		}
+		ob->xspeed = ob->xdir << 5;
+		ob->yspeed = -32;
+		SD_PlaySound(SND_BOBBAJUMP);
+	}
+}
+
+/*
+===========================
+=
+= C_Bobba
+=
+===========================
+*/
+
+void C_Bobba(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+	else if (hit->obclass == stunshotobj)
+	{
+		ExplodeShot(hit);
+		if (hit->xdir != 0)
+		{
+			ob->xdir = -hit->xdir;
+		}
+	}
+}
+
+/*
+===========================
+=
+= R_Bobba
+=
+===========================
+*/
+
+void R_Bobba(objtype *ob)
+{
+	if (ob->hiteast)
+	{
+		ob->xdir = 1;
+		ob->xspeed = -ob->xspeed;
+	}
+	else if (ob->hitwest)
+	{
+		ob->xdir = -1;
+		ob->xspeed = -ob->xspeed;
+	}
+
+	if (ob->hitsouth)
+		ob->yspeed = 0;
+
+	if (ob->hitnorth)
+	{
+		SD_PlaySound(SND_BOBBALAND);
+		ChangeState(ob, &s_bobbastand);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+===========================
+=
+= R_BobbaShot
+=
+===========================
+*/
+
+void R_BobbaShot(objtype *ob)
+{
+	if (ob->hitnorth || ob->hitsouth || ob->hiteast || ob->hitwest)
+	{
+		ChangeState(ob, &s_bobbashotvanish1);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+=============================================================================
+
+						  BABOBBA
+
+temp1 = jump counter (Babobba) / animation counter (Shot)
+
+=============================================================================
+*/
+
+statetype s_babobbajump1       = {BABOBBAL2SPR,     BABOBBAR2SPR,     stepthink, false, false,   8, 0, 0, T_Projectile, C_Babobba, R_Babobba, &s_babobbajump2};
+statetype s_babobbajump2       = {BABOBBAL3SPR,     BABOBBAR3SPR,     think,     false, false,   8, 0, 0, T_Projectile, C_Babobba, R_Babobba, &s_babobbajump2};
+statetype s_babobbastand       = {BABOBBAL1SPR,     BABOBBAR1SPR,     step,      false, false,  20, 0, 0, T_BabobbaStand, C_Babobba, R_Draw, &s_babobbajump1};
+statetype s_babobbaattack      = {BABOBBAL1SPR,     BABOBBAR1SPR,     step,      false, false,  70, 0, 0, NULL, C_Babobba, R_Draw, &s_babobbastand};
+statetype s_babobbastun1       = {BABOBBAL2SPR,     BABOBBAR2SPR,     think,     false, false,   0, 0, 0, T_Projectile, NULL, R_Stunned, &s_babobbastun2};
+statetype s_babobbastun2       = {BABOBBASTUNSPR,   BABOBBASTUNSPR,   think,     false, false,   0, 0, 0, T_Projectile, NULL, R_Stunned, NULL};
+statetype s_babobbasleep1      = {BABOBBASLEEP1SPR, BABOBBASLEEP1SPR, step,      false, false,  15, 0, 0, NULL, C_BabobbaSleep, R_Draw, &s_babobbasleep2};
+statetype s_babobbasleep2      = {BABOBBASLEEP2SPR, BABOBBASLEEP2SPR, step,      false, false,  15, 0, 0, NULL, C_BabobbaSleep, R_Draw, &s_babobbasleep3};
+statetype s_babobbasleep3      = {BABOBBASLEEP3SPR, BABOBBASLEEP3SPR, step,      false, false,  15, 0, 0, NULL, C_BabobbaSleep, R_Draw, &s_babobbasleep4};
+statetype s_babobbasleep4      = {BABOBBASLEEP4SPR, BABOBBASLEEP4SPR, step,      false, false, 500, 0, 0, NULL, C_BabobbaSleep, R_Draw, &s_babobbasleep5};
+statetype s_babobbasleep5      = {BABOBBASLEEP3SPR, BABOBBASLEEP3SPR, step,      false, false,  15, 0, 0, NULL, C_BabobbaSleep, R_Draw, &s_babobbasleep6};
+statetype s_babobbasleep6      = {BABOBBASLEEP2SPR, BABOBBASLEEP2SPR, step,      false, false,  15, 0, 0, NULL, C_BabobbaSleep, R_Draw, &s_babobbasleep7};
+statetype s_babobbasleep7      = {BABOBBASLEEP1SPR, BABOBBASLEEP1SPR, step,      false, false,  15, 0, 0, NULL, C_BabobbaSleep, R_Draw, &s_babobbastand};
+statetype s_babobbashot1       = {BABOBBASHOT1SPR,  BABOBBASHOT1SPR,  think,     false, false,   0, 0, 0, T_Projectile, C_Lethal, R_Bounce, &s_babobbashot2};
+statetype s_babobbashot2       = {BABOBBASHOT2SPR,  BABOBBASHOT2SPR,  step,      false, false,   8, 0, 0, T_BabobbaShot, C_Lethal, R_Draw, &s_babobbashot3};
+statetype s_babobbashot3       = {BABOBBASHOT1SPR,  BABOBBASHOT1SPR,  step,      false, false,   8, 0, 0, NULL, C_Lethal, R_Draw, &s_babobbashot2};
+statetype s_babobbashotvanish1 = {BABOBBASHOT2SPR,  BABOBBASHOT2SPR,  step,      false, false,   8, 0, 0, T_BabobbaShotVanish, C_Lethal, R_Draw, &s_babobbashotvanish2};
+statetype s_babobbashotvanish2 = {-1,               -1,               step,      false, false,   8, 0, 0, NULL, NULL, R_Draw, &s_babobbashotvanish1};
+
+/*
+===========================
+=
+= SpawnBabobba
+=
+===========================
+*/
+
+void SpawnBabobba(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = babobbaobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -2*TILEGLOBAL;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	new->ydir = 1;
+	NewState(new, &s_babobbajump1);
+}
+
+/*
+===========================
+=
+= T_BabobbaStand
+=
+===========================
+*/
+
+void T_BabobbaStand(objtype *ob)
+{
+	Sint16 i;
+	Uint16 far *map;
+
+	if (US_RndT() < 4)
+	{
+		ob->temp1 = 0;
+		ob->state = &s_babobbasleep1;
+	}
+	else if (++ob->temp1 == 3)
+	{
+		ob->temp1 = 0;
+
+		GetNewObj(true);
+		new->active = ac_removable;
+		new->obclass = mshotobj;
+		new->y = ob->y + 4*PIXGLOBAL;
+		new->xdir = ob->xdir;
+		if (ob->xdir == 1)
+		{
+			new->x = ob->x + 16*PIXGLOBAL;
+		}
+		else
+		{
+			new->x = ob->x + 11*PIXGLOBAL;
+		}
+		new->xspeed = new->xdir << 5;
+		NewState(new, &s_babobbashot1);
+		new->priority = 2;
+		ob->state = &s_babobbaattack;
+	}
+	else
+	{
+		map = mapsegs[1] + mapbwidthtable[ob->tilebottom+1]/2 + ob->tilemidx;
+		for (i=0; i<4; map += ob->xdir, i++)
+		{
+			if ( !tinf[*map+NORTHWALL]
+				&& !tinf[*(map-mapwidth)+NORTHWALL]
+				&& !tinf[*(map+mapwidth)+NORTHWALL] )
+			{
+				ob->xdir = -ob->xdir;
+				break;
+			}
+		}
+		ob->xspeed = ob->xdir *24;
+		ob->yspeed = -32;
+	}
+}
+
+/*
+===========================
+=
+= C_Babobba
+=
+===========================
+*/
+
+void C_Babobba(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == keenobj)
+	{
+		KillKeen();
+	}
+	else if (hit->obclass == stunshotobj)
+	{
+		StunObj(ob, hit, &s_babobbastun1);
+	}
+}
+
+/*
+===========================
+=
+= C_BabobbaSleep
+=
+===========================
+*/
+
+void C_BabobbaSleep(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == stunshotobj)
+	{
+		StunObj(ob, hit, &s_babobbastun1);
+	}
+}
+
+/*
+===========================
+=
+= R_Babobba
+=
+===========================
+*/
+
+void R_Babobba(objtype *ob)
+{
+	if (ob->hiteast)
+	{
+		ob->xdir = 1;
+		ob->xspeed = -ob->xspeed;
+	}
+	else if (ob->hitwest)
+	{
+		ob->xdir = -1;
+		ob->xspeed = -ob->xspeed;
+	}
+
+	if (ob->hitsouth)
+		ob->yspeed = 0;
+
+	if (ob->hitnorth)
+	{
+		ChangeState(ob, &s_babobbastand);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+===========================
+=
+= T_BabobbaShot
+=
+===========================
+*/
+
+void T_BabobbaShot(objtype *ob)
+{
+	if (++ob->temp1 == 10)
+	{
+		ob->temp1 = 0;
+		ob->state = &s_babobbashotvanish1;
+	}
+}
+
+/*
+===========================
+=
+= T_BabobbaShotVanish
+=
+===========================
+*/
+
+void T_BabobbaShotVanish(objtype *ob)
+{
+	if (++ob->temp1 == 5)
+	{
+		RemoveObj(ob);
+	}
+}
+
+/*
+=============================================================================
+
+						  BLORB
+
+=============================================================================
+*/
+
+statetype s_blorb1        = {BLORB1SPR, BLORB1SPR, slide, false, false, 20, 8, 8, 0, C_Lethal, R_Blorb, &s_blorb2};
+statetype s_blorb2        = {BLORB2SPR, BLORB2SPR, slide, false, false, 20, 8, 8, 0, C_Lethal, R_Blorb, &s_blorb3};
+statetype s_blorb3        = {BLORB3SPR, BLORB3SPR, slide, false, false, 20, 8, 8, 0, C_Lethal, R_Blorb, &s_blorb1};
+
+/*
+===========================
+=
+= SpawnBlorb
+=
+===========================
+*/
+
+void SpawnBlorb(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = blorbobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = CONVERT_TILE_TO_GLOBAL(tileY) + -8*PIXGLOBAL;
+	if (US_RndT() < 0x80)
+	{
+		new->xdir = 1;
+	}
+	else
+	{
+		new->xdir = -1;
+	}
+	if (US_RndT() < 0x80)
+	{
+		new->ydir = 1;
+	}
+	else
+	{
+		new->ydir = -1;
+	}
+	new->needtoclip = cl_fullclip;
+	NewState(new, &s_blorb1);
+}
+
+/*
+===========================
+=
+= R_Blorb
+=
+===========================
+*/
+
+void R_Blorb(objtype *ob)
+{
+	if (ob->hitnorth)
+	{
+		ob->ydir = -1;
+		SD_PlaySound(SND_BLORBBOUNCE);
+	}
+	else if (ob->hitsouth)
+	{
+		ob->ydir = 1;
+		SD_PlaySound(SND_BLORBBOUNCE);
+	}
+	if (ob->hitwest)
+	{
+		ob->xdir = -1;
+		SD_PlaySound(SND_BLORBBOUNCE);
+	}
+	else if (ob->hiteast)
+	{
+		ob->xdir = 1;
+		SD_PlaySound(SND_BLORBBOUNCE);
+	}
+	RF_PlaceSprite(&ob->sprite, ob->x, ob->y, ob->shapenum, spritedraw, ob->priority);
+}
+
+/*
+=============================================================================
+
+						  CEILICK
+
+temp1 = initial y position
+
+=============================================================================
+*/
+
+statetype s_ceilickhidden   = {TONGUE1SPR,     TONGUE1SPR,     think, false, false, 20, 0,   0, T_CeilickHidden, NULL, R_Draw, NULL};
+statetype s_ceilickattack1  = {TONGUE1SPR,     TONGUE1SPR,     step,  false, false,  6, 0,   0, NULL, NULL, R_Draw, &s_ceilickattack2};
+statetype s_ceilickattack2  = {TONGUE2SPR,     TONGUE2SPR,     step,  false, false,  6, 0,   0, NULL, C_Lethal, R_Draw, &s_ceilickattack3};
+statetype s_ceilickattack3  = {TONGUE3SPR,     TONGUE3SPR,     step,  false, false,  6, 0,   0, NULL, C_Lethal, R_Draw, &s_ceilickattack4};
+statetype s_ceilickattack4  = {TONGUE4SPR,     TONGUE4SPR,     step,  false, false,  6, 0,   0, NULL, C_Lethal, R_Draw, &s_ceilickattack5};
+statetype s_ceilickattack5  = {TONGUE5SPR,     TONGUE5SPR,     step,  false, false,  6, 0,   0, NULL, C_Lethal, R_Draw, &s_ceilickattack6};
+statetype s_ceilickattack6  = {TONGUE4SPR,     TONGUE4SPR,     step,  false, false,  6, 0,   0, NULL, C_Lethal, R_Draw, &s_ceilickattack7};
+statetype s_ceilickattack7  = {TONGUE3SPR,     TONGUE3SPR,     step,  false, false,  6, 0,   0, NULL, C_Lethal, R_Draw, &s_ceilickattack8};
+statetype s_ceilickattack8  = {TONGUE4SPR,     TONGUE4SPR,     step,  false, false,  6, 0,   0, NULL, C_Lethal, R_Draw, &s_ceilickattack9};
+statetype s_ceilickattack9  = {TONGUE5SPR,     TONGUE5SPR,     step,  false, false,  6, 0,   0, NULL, C_Lethal, R_Draw, &s_ceilickattack10};
+statetype s_ceilickattack10 = {TONGUE2SPR,     TONGUE2SPR,     step,  false, false, 10, 0,   0, NULL, C_Lethal, R_Draw, &s_ceilickattack11};
+statetype s_ceilickattack11 = {TONGUE1SPR,     TONGUE1SPR,     step,  false, false, 10, 0,   0, NULL, NULL, R_Draw, &s_ceilicklaugh1};
+statetype s_ceilicklaugh1   = {CEILICK1SPR,    CEILICK1SPR,    slide, true,  false, 16, 0,  16, T_CeilickLaugh, C_Ceilick, R_Draw, &s_ceilicklaugh2};
+statetype s_ceilicklaugh2   = {CEILICK2SPR,    CEILICK2SPR,    step,  true,  false, 10, 0,   0, NULL, C_Ceilick, R_Draw, &s_ceilicklaugh3};
+statetype s_ceilicklaugh3   = {CEILICK1SPR,    CEILICK1SPR,    step,  true,  false, 10, 0,   0, NULL, C_Ceilick, R_Draw, &s_ceilicklaugh4};
+statetype s_ceilicklaugh4   = {CEILICK2SPR,    CEILICK2SPR,    step,  true,  false, 10, 0,   0, NULL, C_Ceilick, R_Draw, &s_ceilicklaugh5};
+statetype s_ceilicklaugh5   = {CEILICK1SPR,    CEILICK1SPR,    step,  true,  false, 10, 0,   0, NULL, C_Ceilick, R_Draw, &s_ceilicklaugh6};
+statetype s_ceilicklaugh6   = {CEILICK2SPR,    CEILICK2SPR,    step,  true,  false, 10, 0,   0, NULL, C_Ceilick, R_Draw, &s_ceilicklaugh7};
+statetype s_ceilicklaugh7   = {CEILICK1SPR,    CEILICK1SPR,    step,  true,  false, 10, 0,   0, NULL, C_Ceilick, R_Draw, &s_ceilicklaugh8};
+statetype s_ceilicklaugh8   = {CEILICK1SPR,    CEILICK1SPR,    slide, true,  false, 16, 0, -16, NULL, C_Ceilick, R_Draw, &s_ceilicklaugh9};
+statetype s_ceilicklaugh9   = {-1,             -1,             step,  true,  false, 60, 0,   0, NULL, C_Ceilick, R_Draw, &s_ceilickhidden};
+statetype s_ceilickstun     = {CEILICKSTUNSPR, CEILICKSTUNSPR, think, true,  false,  0, 0,   0, T_CeilickStunned, NULL, R_Stunned, NULL};
+
+/*
+===========================
+=
+= SpawnCeilick
+=
+===========================
+*/
+
+void SpawnCeilick(Uint16 tileX, Uint16 tileY)
+{
+	GetNewObj(false);
+	new->obclass = ceilickobj;
+	new->active = ac_yes;
+	new->priority = 0;
+	new->needtoclip = cl_noclip;
+	new->x = CONVERT_TILE_TO_GLOBAL(tileX);
+	new->y = new->temp1 = CONVERT_TILE_TO_GLOBAL(tileY);
+	new->ydir = 1;
+	NewState(new, &s_ceilickhidden);
+}
+
+/*
+===========================
+=
+= T_CeilickHidden
+=
+===========================
+*/
+
+void T_CeilickHidden(objtype *ob)
+{
+	if ( player->y - ob->y <= 40*PIXGLOBAL
+		&& player->left < ob->right+PIXGLOBAL
+		&& player->right > ob->left-PIXGLOBAL )
+	{
+		SD_PlaySound(SND_CEILICKATTACK);
+		ob->state = &s_ceilickattack1;
+	}
+}
+
+/*
+===========================
+=
+= T_CeilickLaugh
+=
+===========================
+*/
+
+#pragma argsused
+void T_CeilickLaugh(objtype *ob)
+{
+	SD_PlaySound(SND_CEILICKLAUGH);
+}
+
+/*
+===========================
+=
+= T_CeilickStunned
+=
+===========================
+*/
+
+void T_CeilickStunned(objtype *ob)
+{
+	ob->needtoreact = true;	// to make sure the stunned stars animate
+}
+
+/*
+===========================
+=
+= C_Ceilick
+=
+===========================
+*/
+
+void C_Ceilick(objtype *ob, objtype *hit)
+{
+	if (hit->obclass == stunshotobj)
+	{
+		ob->y = ob->temp1;
+		ExplodeShot(hit);
+		ob->temp1 = ob->temp2 = ob->temp3 = 0;
+		ob->temp4 = ob->obclass;
+		ChangeState(ob, &s_ceilickstun);
+		ob->obclass = stunnedobj;
+	}
+}
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/KEEN6/K6_DEF.H b/16/keen456/KEEN4-6/KEEN6/K6_DEF.H
new file mode 100755
index 00000000..9453b52c
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN6/K6_DEF.H
@@ -0,0 +1,518 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+#ifndef __K6_DEF__
+#define __K6_DEF__
+
+/*
+=============================================================================
+
+						GLOBAL CONSTANTS
+
+=============================================================================
+*/
+
+#if GRMODE == CGAGR
+#define MINMEMORY 255000l
+#else
+#define MINMEMORY 300000l
+#endif
+
+#define STARPALETTE   {0, 1, 24, 25, 4, 28, 6, 7, 31, 31, 31, 31, 31, 31, 31, 31, 0}
+#define INTROPALETTE  {0, 5, 5, 21, 1, 1, 1, 1, 17, 17, 17, 17, 19, 19, 19, 19, 0}
+#define SHRINKPALETTE {0, 5, 5, 21, 1, 1, 1, 1, 17, 17, 17, 17, 19, 19, 19,  5, 0}
+
+#define HIGHSCORE_LEFT	40
+#define HIGHSCORE_TOP	51
+#define HIGHSCORE_RIGHT	280
+#define HIGHSCORE_MAP	18
+
+#define STATUS_PRESSKEY_X 120
+
+#define WORLDMAPNAME	"Fribbulus Xax"
+#define DROPSNAME	"VIVAS"
+
+#define STARWARSMUSIC	13
+#define ENDINGMUSIC	1
+
+// levels in this range can NOT be re-entered (BWB level should be > MAXDONELEVEL)
+#define MINDONELEVEL 1
+#define MAXDONELEVEL 16
+
+#define INACTIVATEDIST 4
+
+//
+// tiles for worldmap teleporters
+//
+#define TELEPORTERTILE1 2613	// tile animation for teleporting out
+#define TELEPORTERTILE2 2629	// tile after teleporting out
+#define TELEPORTERTILE3 TELEPORTERTILE1	// tile animation for teleporting in
+#define TELEPORTERTILE4 TELEPORTERTILE2	// tile after teleporting in
+
+#define TELEPORERTILEMASK 3	// animation has 4 frames
+
+extern Sint16 groundslam;
+
+//HACKs:
+//#define US_ManualCheck() true
+boolean US_ManualCheck(void);
+
+/*
+=============================================================================
+
+						K6_SPEC DEFINITIONS
+
+=============================================================================
+*/
+
+extern char far swtext[];
+extern char far *levelnames[GAMELEVELS];
+extern char far *levelenter[GAMELEVELS];
+
+void ScanInfoPlane(void);
+
+extern statetype s_keenstun;
+
+void FlipBigSwitch(objtype *ob, boolean isup);
+void GotSandwich(void);
+void GotHook(void);
+void GotPasscard(void);
+
+
+/*
+=============================================================================
+
+						K6_ACT1 DEFINITIONS
+
+=============================================================================
+*/
+
+extern Sint16 pdirx[];
+extern Sint16 pdiry[];
+
+void C_ClipSide(objtype *ob, objtype *hit);
+void C_ClipTop(objtype *ob, objtype *hit);
+void R_Land(objtype *ob);
+void R_Bounce(objtype *ob);
+
+extern statetype s_bonus1;
+extern statetype s_bonus2;
+extern statetype s_bonusfly1;
+extern statetype s_bonusfly2;
+extern statetype s_bonusrise;
+
+extern statetype s_splash1;
+extern statetype s_splash2;
+extern statetype s_splash3;
+extern statetype s_splash4;
+
+extern Uint16 bonusshape[];
+
+void SpawnBonus(Uint16 tileX, Uint16 tileY, Uint16 type);
+void SpawnSplash(Uint16 tileX, Uint16 tileY);
+void T_Bonus(objtype *ob);
+void T_FlyBonus(objtype *ob);
+
+extern statetype s_grabbiter1;
+extern statetype s_grabbiter2;
+extern statetype s_grabbitersleep1;
+extern statetype s_grabbitersleep2;
+
+void SpawnGrabbiter(Uint16 tileX, Uint16 tileY);
+void C_Grabbiter(objtype *ob, objtype *hit);
+
+extern statetype s_rocket;
+extern statetype s_rocketfly1;
+extern statetype s_rocketfly2;
+extern statetype s_keenrocket;
+
+void SpawnRocket(Uint16 tileX, Uint16 tileY, Uint16 state);
+void T_Rocket(objtype *ob);
+void C_Rocket(objtype *ob, objtype *hit);
+void C_RocketFly(objtype *ob, objtype *hit);
+void T_RocketFly(objtype *ob);
+
+extern statetype s_grapplespot;
+extern statetype s_throwrope1;
+extern statetype s_throwrope2;
+extern statetype s_climbrope1;
+extern statetype s_climbrope2;
+extern statetype s_maprope;
+extern statetype s_mapropeshort;
+
+void SpawnGrappleSpot(Uint16 tileX, Uint16 tileY, Uint16 type);
+void T_ThrowRope(objtype *ob);
+void T_ClimbRope(objtype *ob);
+void C_GrappleSpot(objtype *ob, objtype *hit);
+
+extern statetype s_satellitestopspot;
+extern statetype s_worldkeensatellite;
+extern statetype s_satellite1;
+extern statetype s_satellite2;
+extern statetype s_satellite3;
+extern statetype s_satellite4;
+
+void SpawnSatelliteStop(Uint16 tileX, Uint16 tileY, Uint16 type);
+void SpawnSatellite(Uint16 tileX, Uint16 tileY);
+void T_Satellite(objtype *ob);
+void C_Satellite(objtype *ob, objtype *hit);
+void R_WorldKeenSatellite(objtype *ob);
+
+extern statetype s_sandwich;
+
+void SpawnSandwich(Uint16 tileX, Uint16 tileY);
+
+extern statetype s_hook;
+
+void SpawnHook(Uint16 tileX, Uint16 tileY);
+
+extern statetype s_passcard;
+
+void SpawnPasscard(Uint16 tileX, Uint16 tileY);
+void C_Molly(objtype *ob, objtype *hit);
+
+extern statetype s_molly1;
+extern statetype s_molly2;
+extern statetype s_molly3;
+extern statetype s_molly4;
+
+void SpawnMolly(Uint16 tileX, Uint16 tileY);
+
+extern statetype s_platform;
+
+void SpawnPlatform(Uint16 tileX, Uint16 tileY, Sint16 dir);
+void T_Platform(objtype *ob);
+
+extern statetype s_dropplatsit;
+extern statetype s_fallplatfall;
+extern statetype s_fallplatrise;
+
+void SpawnDropPlat(Uint16 tileX, Uint16 tileY);
+void T_DropPlatSit(objtype *ob);
+void T_DropPlatFall(objtype *ob);
+void T_DropPlatRise(objtype *ob);
+
+extern statetype s_staticplatform;
+
+void SpawnStaticPlat(Uint16 tileX, Uint16 tileY);
+
+extern statetype s_goplat;
+
+void SpawnGoPlat(Uint16 tileX, Uint16 tileY, Sint16 dir);
+void T_GoPlat(objtype *ob);
+void R_GoPlat(objtype *ob);
+
+extern statetype s_sneakplatsit;
+extern statetype s_sneakplatdodge;
+extern statetype s_sneakplatreturn;
+
+void SpawnSneakPlat(Uint16 tileX, Uint16 tileY);
+void T_SneakPlat(objtype *ob);
+
+extern statetype s_bloogwalk1;
+extern statetype s_bloogwalk2;
+extern statetype s_bloogwalk3;
+extern statetype s_bloogwalk4;
+extern statetype s_bloogstun;
+
+void SpawnBloog(Uint16 tileX, Uint16 tileY);
+void T_BloogWalk(objtype *ob);
+void C_Bloog(objtype *ob, objtype *hit);
+
+extern statetype s_blooguardwalk1;
+extern statetype s_blooguardwalk2;
+extern statetype s_blooguardwalk3;
+extern statetype s_blooguardwalk4;
+extern statetype s_blooguardattack1;
+extern statetype s_blooguardattack2;
+extern statetype s_blooguardattack3;
+extern statetype s_blooguardattack4;
+extern statetype s_blooguardstun;
+
+void SpawnBlooguard(Uint16 tileX, Uint16 tileY);
+void T_BlooguardWalk(objtype *ob);
+void T_BlooguardAttack(objtype *ob);
+void C_Blooguard(objtype *ob, objtype *hit);
+void R_Blooguard(objtype *ob);
+
+extern statetype s_rbloogletwalk1;
+extern statetype s_rbloogletwalk2;
+extern statetype s_rbloogletwalk3;
+extern statetype s_rbloogletwalk4;
+extern statetype s_rbloogletstun;
+extern statetype s_ybloogletwalk1;
+extern statetype s_ybloogletwalk2;
+extern statetype s_ybloogletwalk3;
+extern statetype s_ybloogletwalk4;
+extern statetype s_ybloogletstun;
+extern statetype s_bbloogletwalk1;
+extern statetype s_bbloogletwalk2;
+extern statetype s_bbloogletwalk3;
+extern statetype s_bbloogletwalk4;
+extern statetype s_bbloogletstun;
+extern statetype s_gbloogletwalk1;
+extern statetype s_gbloogletwalk2;
+extern statetype s_gbloogletwalk3;
+extern statetype s_gbloogletwalk4;
+extern statetype s_gbloogletstun;
+
+void SpawnBlooglet(Uint16 tileX, Uint16 tileY, Sint16 type);
+void C_Blooglet(objtype *ob, objtype *hit);
+
+/*
+=============================================================================
+
+						K6_ACT2 DEFINITIONS
+
+=============================================================================
+*/
+
+extern statetype s_nospikestand;
+extern statetype s_nospikewalk1;
+extern statetype s_nospikewalk2;
+extern statetype s_nospikewalk3;
+extern statetype s_nospikewalk4;
+extern statetype s_nospikerun1;
+extern statetype s_nospikerun2;
+extern statetype s_nospikerun3;
+extern statetype s_nospikerun4;
+extern statetype s_nospikeconfused1;
+extern statetype s_nospikeconfused2;
+extern statetype s_nospikeconfused3;
+extern statetype s_nospikefall;
+extern statetype s_nospikestun;
+
+void SpawnNospike(Uint16 tileX, Uint16 tileY);
+void T_NospikeWalk(objtype *ob);
+void T_NospikeRun(objtype *ob);
+void C_Nospike(objtype *ob, objtype *hit);
+void T_NospikeConfused(objtype* ob);
+void R_NospikeConfused(objtype *ob);
+void R_NospikeFall(objtype *ob);
+void R_NospikeRun(objtype *ob);
+
+extern statetype s_gikwalk1;
+extern statetype s_gikwalk2;
+extern statetype s_gikwalk3;
+extern statetype s_gikjump;
+extern statetype s_gikslide1;
+extern statetype s_gikslide2;
+extern statetype s_gikstand;
+
+void SpawnGik(Uint16 tileX, Uint16 tileY);
+void T_GikWalk(objtype *ob);
+void T_GikSlide(objtype *ob);
+void R_GikJump(objtype *ob);
+void R_GikSlide(objtype *ob);
+
+extern statetype s_cannon;
+extern statetype s_cannonfire;
+extern statetype s_cshot1;
+extern statetype s_cshot2;
+extern statetype s_cshot3;
+extern statetype s_cshot4;
+extern statetype s_cshothit1;
+extern statetype s_cshothit2;
+
+void SpawnCannon(Uint16 tileX, Uint16 tileY, Sint16 dir);
+void T_Cannon(objtype *ob);
+void C_CShot(objtype *ob, objtype *hit);
+void R_CShot(objtype *ob);
+
+extern statetype s_orbatrix1;
+extern statetype s_orbatrix2;
+extern statetype s_orbatrixcurl1;
+extern statetype s_orbatrixcurl2;
+extern statetype s_orbatrixcurl3;
+extern statetype s_orbatrixuncurl1;
+extern statetype s_orbatrixuncurl2;
+extern statetype s_orbatrixidle1;
+extern statetype s_orbatrixidle2;
+extern statetype s_orbatrixidle3;
+extern statetype s_orbatrixidle4;
+extern statetype s_orbatrixbounce1;
+extern statetype s_orbatrixbounce2;
+extern statetype s_orbatrixbounce3;
+extern statetype s_orbatrixbounce4;
+
+void SpawnOrbatrix(Uint16 tileX, Uint16 tileY);
+void T_OrbatrixFly(objtype *ob);
+void C_Orbatrix(objtype *ob, objtype *hit);
+void R_Orbatrix(objtype *ob);
+void R_OrbatrixBounce(objtype *ob);
+void T_OrbatrixCurl(objtype *ob);
+void T_OrbatrixUncurl(objtype *ob);
+void C_OrbatrixBounce(objtype *ob, objtype *hit);
+
+extern statetype s_bipstand;
+extern statetype s_bipwalk1;
+extern statetype s_bipwalk2;
+extern statetype s_bipwalk3;
+extern statetype s_bipwalk4;
+extern statetype s_bipsquished;
+
+void T_BipWalk(objtype *ob);
+void C_Bip(objtype *ob, objtype *hit);
+
+extern statetype s_bipship;
+extern statetype s_bipshipshot;
+extern statetype s_bipshipturn1;
+extern statetype s_bipshipturn2;
+extern statetype s_bipshipturn3;
+extern statetype s_bipshipturn4;
+extern statetype s_bipshipexplode1;
+extern statetype s_bipshipexplode2;
+extern statetype s_bipshipexplode3;
+extern statetype s_bipshipsmoke1;
+extern statetype s_bipshipsmoke2;
+
+void SpawnBipship(Uint16 tileX, Uint16 tileY);
+void R_BipShot(objtype *ob);
+void T_BipshipTurn(objtype *ob);
+void T_BipshipFly(objtype *ob);
+void T_BipshipExplode(objtype *ob);
+void C_Bipship(objtype *ob, objtype *hit);
+
+extern statetype s_flectstand;
+extern statetype s_flectturn;
+extern statetype s_flectwalk1;
+extern statetype s_flectwalk2;
+extern statetype s_flectwalk3;
+extern statetype s_flectwalk4;
+extern statetype s_flectstun;
+
+void SpawnFlect(Uint16 tileX, Uint16 tileY);
+void T_FlectStand(objtype *ob);
+void T_FlectWalk(objtype *ob);
+void C_Flect(objtype *ob, objtype *hit);
+void R_Flect(objtype *ob);
+
+/*
+=============================================================================
+
+						K6_ACT3 DEFINITIONS
+
+=============================================================================
+*/
+
+extern statetype s_fleexwalk1;
+extern statetype s_fleexwalk2;
+extern statetype s_fleexrun1;
+extern statetype s_fleexrun2;
+extern statetype s_fleexrun3;
+extern statetype s_fleexrun4;
+extern statetype s_fleexlook1;
+extern statetype s_fleexlook2;
+extern statetype s_fleexstun;
+
+void SpawnFleex(Uint16 tileX, Uint16 tileY);
+void T_FleexWalk(objtype *ob);
+void T_FleexLook(objtype *ob);
+void C_Fleex(objtype *ob, objtype *hit);
+
+extern statetype s_bobbajump1;
+extern statetype s_bobbajump2;
+extern statetype s_bobbastand;
+extern statetype s_bobbaattack;
+extern statetype s_bobbashot1;
+extern statetype s_bobbashot2;
+extern statetype s_bobbashot3;
+extern statetype s_bobbashot4;
+extern statetype s_bobbashot5;
+extern statetype s_bobbashot6;
+extern statetype s_bobbashot7;
+extern statetype s_bobbashot8;
+extern statetype s_bobbashotvanish1;
+extern statetype s_bobbashotvanish2;
+extern statetype s_bobbashotvanish3;
+
+void SpawnBobba(Uint16 tileX, Uint16 tileY);
+void T_BobbaShot(objtype *ob);
+void T_BobbaStand(objtype *ob);
+void C_Bobba(objtype *ob, objtype *hit);
+void R_Bobba(objtype *ob);
+void R_BobbaShot(objtype *ob);
+
+extern statetype s_babobbajump1;
+extern statetype s_babobbajump2;
+extern statetype s_babobbastand;
+extern statetype s_babobbaattack;
+extern statetype s_babobbastun1;
+extern statetype s_babobbastun2;
+extern statetype s_babobbasleep1;
+extern statetype s_babobbasleep2;
+extern statetype s_babobbasleep3;
+extern statetype s_babobbasleep4;
+extern statetype s_babobbasleep5;
+extern statetype s_babobbasleep6;
+extern statetype s_babobbasleep7;
+extern statetype s_babobbashot1;
+extern statetype s_babobbashot2;
+extern statetype s_babobbashot3;
+extern statetype s_babobbashotvanish1;
+extern statetype s_babobbashotvanish2;
+
+void SpawnBabobba(Uint16 tileX, Uint16 tileY);
+void T_BabobbaStand(objtype *ob);
+void C_Babobba(objtype *ob, objtype *hit);
+void C_BabobbaSleep(objtype *ob, objtype *hit);
+void R_Babobba(objtype *ob);
+void T_BabobbaShot(objtype *ob);
+void T_BabobbaShotVanish(objtype *ob);
+
+extern statetype s_blorb1;
+extern statetype s_blorb2;
+extern statetype s_blorb3;
+
+void SpawnBlorb(Uint16 tileX, Uint16 tileY);
+void R_Blorb(objtype *ob);
+
+extern statetype s_ceilickhidden;
+extern statetype s_ceilickattack1;
+extern statetype s_ceilickattack2;
+extern statetype s_ceilickattack3;
+extern statetype s_ceilickattack4;
+extern statetype s_ceilickattack5;
+extern statetype s_ceilickattack6;
+extern statetype s_ceilickattack7;
+extern statetype s_ceilickattack8;
+extern statetype s_ceilickattack9;
+extern statetype s_ceilickattack10;
+extern statetype s_ceilickattack11;
+extern statetype s_ceilicklaugh1;
+extern statetype s_ceilicklaugh2;
+extern statetype s_ceilicklaugh3;
+extern statetype s_ceilicklaugh4;
+extern statetype s_ceilicklaugh5;
+extern statetype s_ceilicklaugh6;
+extern statetype s_ceilicklaugh7;
+extern statetype s_ceilicklaugh8;
+extern statetype s_ceilicklaugh9;
+extern statetype s_ceilickstun;
+
+void SpawnCeilick(Uint16 tileX, Uint16 tileY);
+void T_CeilickHidden(objtype *ob);
+void T_CeilickLaugh(objtype *ob);
+void T_CeilickStunned(objtype *ob);
+void C_Ceilick(objtype *ob, objtype *hit);
+
+#endif
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/KEEN6/K6_SPEC.C b/16/keen456/KEEN4-6/KEEN6/K6_SPEC.C
new file mode 100755
index 00000000..ab7c1d14
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN6/K6_SPEC.C
@@ -0,0 +1,887 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is loosely based on:
+ * Keen Dreams Source Code
+ * Copyright (C) 2014 Javier M. Chavez
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+/*
+K6_SPEC.C
+=========
+
+Contains (in this order):
+
+- lump definition
+- "Star Wars" crawl text
+- level names & messages
+- ScanInfoPlane() - for spawning the level objects and marking required sprites
+- stunned state for Keen
+- code to flip the big yellow switches
+- messages for sandwich, rope and passcard
+*/
+
+#include "CK_DEF.H"
+
+enum {
+	CONTROLS_LUMP,    //  0
+	KEEN_LUMP,        //  1
+	SUGAR1_LUMP,      //  2
+	SUGAR2_LUMP,      //  3
+	SUGAR3_LUMP,      //  4
+	SUGAR4_LUMP,      //  5
+	SUGAR5_LUMP,      //  6
+	SUGAR6_LUMP,      //  7
+	ONEUP_LUMP,       //  8
+	KEYGEM_LUMP,      //  9
+	AMMO_LUMP,        // 10
+	WORLDKEEN_LUMP,   // 11
+	UNUSED1_LUMP,     // 12
+	BLOOG_LUMP,       // 13
+	RBLOOGLET_LUMP,   // 14
+	YBLOOGLET_LUMP,   // 15
+	BBLOOGLET_LUMP,   // 16
+	GBLOOGLET_LUMP,   // 17
+	PLATFORM_LUMP,    // 18
+	GIK_LUMP,         // 19
+	BLORB_LUMP,       // 20
+	BOBBA_LUMP,       // 21
+	BABOBBA_LUMP,     // 22
+	BLOOGUARD_LUMP,   // 23
+	FLECT_LUMP,       // 24
+	BIP_LUMP,         // 25
+	BIPSQUISHED_LUMP, // 26
+	BIPSHIP_LUMP,     // 27
+	NOSPIKE_LUMP,     // 28
+	ORBATRIX_LUMP,    // 29
+	CEILICK_LUMP,     // 30
+	FLEEX_LUMP,       // 31
+	HOOK_LUMP,        // 32
+	SANDWICH_LUMP,    // 33
+	LASER_LUMP,       // 34
+	PASSCARD_LUMP,    // 35
+	MOLLY_LUMP,       // 36
+
+	NUMLUMPS=40       // Keen 6 has 3 unused lumps at the end
+};
+
+Uint16 lumpstart[NUMLUMPS] = {
+	CONTROLS_LUMP_START,
+	KEEN_LUMP_START,
+	SUGAR1_LUMP_START,
+	SUGAR2_LUMP_START,
+	SUGAR3_LUMP_START,
+	SUGAR4_LUMP_START,
+	SUGAR5_LUMP_START,
+	SUGAR6_LUMP_START,
+	ONEUP_LUMP_START,
+	KEYGEM_LUMP_START,
+	AMMO_LUMP_START,
+	WORLDKEEN_LUMP_START,
+	0,
+	BLOOG_LUMP_START,
+	RBLOOGLET_LUMP_START,
+	YBLOOGLET_LUMP_START,
+	BBLOOGLET_LUMP_START,
+	GBLOOGLET_LUMP_START,
+	PLATFORM_LUMP_START,
+	GIK_LUMP_START,
+	BLORB_LUMP_START,
+	BOBBA_LUMP_START,
+	BABOBBA_LUMP_START,
+	BLOOGUARD_LUMP_START,
+	FLECT_LUMP_START,
+	BIP_LUMP_START,
+	BIPSQUISHED_LUMP_START,
+	BIPSHIP_LUMP_START,
+	NOSPIKE_LUMP_START,
+	ORBATRIX_LUMP_START,
+	CEILICK_LUMP_START,
+	FLEEX_LUMP_START,
+	HOOK_LUMP_START,
+	SANDWICH_LUMP_START,
+	LASER_LUMP_START,
+	PASSCARD_LUMP_START,
+	MOLLY_LUMP_START
+};
+
+Uint16 lumpend[NUMLUMPS] = {
+	CONTROLS_LUMP_END,
+	KEEN_LUMP_END,
+	SUGAR1_LUMP_END,
+	SUGAR2_LUMP_END,
+	SUGAR3_LUMP_END,
+	SUGAR4_LUMP_END,
+	SUGAR5_LUMP_END,
+	SUGAR6_LUMP_END,
+	ONEUP_LUMP_END,
+	KEYGEM_LUMP_END,
+	AMMO_LUMP_END,
+	WORLDKEEN_LUMP_END,
+	0,
+	BLOOG_LUMP_END,
+	RBLOOGLET_LUMP_END,
+	YBLOOGLET_LUMP_END,
+	BBLOOGLET_LUMP_END,
+	GBLOOGLET_LUMP_END,
+	PLATFORM_LUMP_END,
+	GIK_LUMP_END,
+	BLORB_LUMP_END,
+	BOBBA_LUMP_END,
+	BABOBBA_LUMP_END,
+	BLOOGUARD_LUMP_END,
+	FLECT_LUMP_END,
+	BIP_LUMP_END,
+	BIPSQUISHED_LUMP_END,
+	BIPSHIP_LUMP_END,
+	NOSPIKE_LUMP_END,
+	ORBATRIX_LUMP_END,
+	CEILICK_LUMP_END,
+	FLEEX_LUMP_END,
+	HOOK_LUMP_END,
+	SANDWICH_LUMP_END,
+	LASER_LUMP_END,
+	PASSCARD_LUMP_END,
+	MOLLY_LUMP_END
+};
+
+boolean lumpneeded[NUMLUMPS];
+
+#if GRMODE == EGAGR
+
+char far swtext[] =
+	"Episode Six\n"
+	"\n"
+	"Aliens Ate My\n"
+	"Baby Sitter!\n"
+	"\n"
+	"While out in his\n"
+	"backyard clubhouse,\n"
+	"Billy's baby sitter\n"
+	"Molly calls him for\n"
+	"dinner. He continues\n"
+	"working on his new\n"
+	"wrist computer.\n"
+	"\n"
+	"Suddenly, there is a\n"
+	"loud noise outside.\n"
+	"\n"
+	"Rushing out, Keen finds\n"
+	"his baby sitter gone\n"
+	"and a note on a patch\n"
+	"of scorched grass.  The\n"
+	"Bloogs of Fribbulus Xax\n"
+	"are going to make a\n"
+	"meal out of Molly!\n"
+	"\n"
+	"You've got to rescue\n"
+	"her, because your\n"
+	"parents will never\n"
+	"believe you when you\n"
+	"tell them...\n"
+	"\n"
+	"\"Aliens Ate My\n"
+	"Baby Sitter!\"\n";
+
+#endif
+
+char far l0n[] = "Fribbulus Xax";
+char far l1n[] = "Bloogwaters\nCrossing";
+char far l2n[] = "Guard Post One";
+char far l3n[] = "First Dome\nof Darkness";
+char far l4n[] = "Second Dome\nof Darkness";
+char far l5n[] = "The Bloogdome";
+char far l6n[] = "Bloogton Mfg.,\nIncorporated";
+char far l7n[] = "Bloogton Tower";
+char far l8n[] = "Bloogfoods, Inc.";
+char far l9n[] = "Guard Post Two";
+char far l10n[] = "Bloogville";
+char far l11n[] = "BASA";
+char far l12n[] = "Guard Post Three";
+char far l13n[] = "Bloogbase Rec\nDistrict";
+char far l14n[] = "Bloogbase Mgmt.\nDistrict";
+char far l15n[] = "Bloog Control Center";
+char far l16n[] = "Blooglab";
+char far l17n[] = "Bean-with-Bacon\nMegarocket";
+char far l18n[] = "High Scores";
+
+char far l0e[] = "Keen attacks\nFribbulus Xax";
+char far l1e[] = "Keen hops across\nBloogwaters\nCrossing";
+char far l2e[] = "Keen fights his way\nthrough Guard Post One";
+char far l3e[] = "Keen crosses into the\nFirst Dome of Darkness";
+char far l4e[] = "Keen dares to enter the\nSecond Dome of Darkness";
+char far l5e[] = "Keen foolishly enters\nthe Bloogdome";
+char far l6e[] = "Keen makes his way\ninto Bloogton\nManufacturing";
+char far l7e[] = "Keen ascends\nBloogton Tower";
+char far l8e[] = "Keen hungrily enters\nBloogfoods, Inc.";
+char far l9e[] = "Keen smashes through\nGuard Post Two";
+char far l10e[] = "Keen seeks thrills\nin Bloogville";
+char far l11e[] = "Keen rockets into the\nBloog Aeronautics and\nSpace Administration";
+char far l12e[] = "Keen boldly assaults\nGuard Post Three";
+char far l13e[] = "Keen whoops it up in\nthe Bloogbae\nRecreational District";	// sic!
+char far l14e[] = "Keen purposefully struts\ninto the Bloogbase\nManagement District";
+char far l15e[] = "Keen bravely enters the\nBloog Control Center,\nlooking for Molly";
+char far l16e[] = "Keen warily enters\nBlooglab Space\nStation";
+char far l17e[] = "Keen returns to the\nBean-with-Bacon\nMegarocket";
+char far l18e[] = "Keen is in the High\nScore screen. Call Id!";
+
+char far *levelnames[GAMELEVELS] = {
+	l0n,
+	l1n,
+	l2n,
+	l3n,
+	l4n,
+	l5n,
+	l6n,
+	l7n,
+	l8n,
+	l9n,
+	l10n,
+	l11n,
+	l12n,
+	l13n,
+	l14n,
+	l15n,
+	l16n,
+	l17n,
+	l18n
+};
+
+char far *levelenter[GAMELEVELS] = {
+	l0e,
+	l1e,
+	l2e,
+	l3e,
+	l4e,
+	l5e,
+	l6e,
+	l7e,
+	l8e,
+	l9e,
+	l10e,
+	l11e,
+	l12e,
+	l13e,
+	l14e,
+	l15e,
+	l16e,
+	l17e,
+	l18e
+};
+
+Uint16 bonuslump[] = {
+	KEYGEM_LUMP, KEYGEM_LUMP, KEYGEM_LUMP, KEYGEM_LUMP,
+	SUGAR1_LUMP, SUGAR2_LUMP, SUGAR3_LUMP,
+	SUGAR4_LUMP, SUGAR5_LUMP, SUGAR6_LUMP,
+	ONEUP_LUMP, AMMO_LUMP, AMMO_LUMP, 0, 0
+};
+
+//============================================================================
+
+/*
+==========================
+=
+= ScanInfoPlane
+=
+= Spawn all actors and mark down special places
+=
+==========================
+*/
+
+void ScanInfoPlane(void)
+{
+	Uint16 i, x, y, chunk;
+	Sint16 info;
+	Uint16 far *map;
+	objtype *ob;
+
+	InitObjArray();                  // start spawning things with a clean slate
+
+	memset(lumpneeded, 0, sizeof(lumpneeded));
+	map = mapsegs[2];
+
+	for (y=0; y<mapheight; y++)
+	{
+		for (x=0; x<mapwidth; x++)
+		{
+			info = *map++;
+
+			if (info == 0)
+				continue;
+
+			switch (info)
+			{
+			case 1:
+				SpawnKeen(x, y, 1);
+				SpawnScore();
+				lumpneeded[KEEN_LUMP] = true;
+				CA_MarkGrChunk(SCOREBOXSPR);
+				break;
+
+			case 2:
+				SpawnKeen(x, y, -1);
+				SpawnScore();
+				lumpneeded[KEEN_LUMP] = true;
+				CA_MarkGrChunk(SCOREBOXSPR);
+				break;
+
+			case 3:
+				SpawnWorldKeen(x, y);
+				SpawnScore();
+				lumpneeded[WORLDKEEN_LUMP] = true;
+				CA_MarkGrChunk(SCOREBOXSPR);
+				break;
+
+			case 6:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 5:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 4:
+				SpawnBloog(x, y);
+				lumpneeded[BLOOG_LUMP] = true;
+				break;
+
+			case 7:
+			case 8:
+			case 9:
+			case 10:
+			case 11:
+			case 12:
+			case 13:
+			case 14:
+				SpawnBlooglet(x, y, info-7);
+				lumpneeded[(info-7) % 4 + RBLOOGLET_LUMP] = true;
+				if (info > 10)
+					lumpneeded[KEYGEM_LUMP] = true;
+				break;
+
+			case 15:
+			case 16:
+				SpawnGrappleSpot(x, y, info-15);
+				break;
+
+			// case 17 is not used
+
+			case 20:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 19:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 18:
+				SpawnFleex(x, y);
+				lumpneeded[FLEEX_LUMP] = true;
+				break;
+
+			case 21:
+			case 22:
+			case 23:
+			case 24:
+				SpawnMolly(x, y);
+				lumpneeded[MOLLY_LUMP] = true;
+				break;
+
+			case 25:
+				RF_SetScrollBlock(x, y, true);
+				break;
+
+			case 26:
+				RF_SetScrollBlock(x, y, false);
+				break;
+
+			case 27:
+			case 28:
+			case 29:
+			case 30:
+				SpawnPlatform(x, y, info-27);
+				lumpneeded[PLATFORM_LUMP] = true;
+				break;
+
+			// case 31 is the block icon
+
+			case 32:
+				SpawnDropPlat(x, y);
+				lumpneeded[PLATFORM_LUMP] = true;
+				break;
+
+			case 35:
+				SpawnStaticPlat(x, y);
+				lumpneeded[PLATFORM_LUMP] = true;
+				break;
+			case 34:
+				if (gamestate.difficulty > gd_Normal)
+					break;
+				SpawnStaticPlat(x, y);
+				lumpneeded[PLATFORM_LUMP] = true;
+				break;
+			case 33:
+				if (gamestate.difficulty > gd_Easy)
+					break;
+				SpawnStaticPlat(x, y);
+				lumpneeded[PLATFORM_LUMP] = true;
+				break;
+
+			case 36:
+			case 37:
+			case 38:
+			case 39:
+				SpawnGoPlat(x, y, info-36);
+				lumpneeded[PLATFORM_LUMP] = true;
+				lumpneeded[BIPSQUISHED_LUMP] = true;	// why?
+				break;
+
+			case 40:
+				SpawnSneakPlat(x, y);
+				lumpneeded[PLATFORM_LUMP] = true;
+				break;
+
+			case 43:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 42:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 41:
+				SpawnBobba(x, y);
+				lumpneeded[BOBBA_LUMP] = true;
+				break;
+
+			case 44:
+			case 45:
+				SpawnSatelliteStop(x, y, info-44);
+				break;
+
+			// case 46 is not used
+
+			case 49:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 48:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 47:
+				SpawnNospike(x, y);
+				lumpneeded[NOSPIKE_LUMP] = true;
+				break;
+
+			case 52:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 51:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 50:
+				SpawnGik(x, y);
+				lumpneeded[GIK_LUMP] = true;
+				break;
+
+			case 53:
+			case 54:
+			case 55:
+			case 56:
+				SpawnCannon(x, y, info-53);
+				lumpneeded[LASER_LUMP] = true;
+				break;
+
+			case 69:
+				if (gamestate.ammo >= 5)
+					break;
+				info = 68;
+				// no break here!
+			case 57:
+			case 58:
+			case 59:
+			case 60:
+			case 61:
+			case 62:
+			case 63:
+			case 64:
+			case 65:
+			case 66:
+			case 67:
+			case 68:
+				SpawnBonus(x, y, info-57);
+				lumpneeded[bonuslump[info-57]] = true;
+				break;
+
+			case 72:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 71:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 70:
+				SpawnOrbatrix(x, y);
+				lumpneeded[ORBATRIX_LUMP] = true;
+				break;
+
+			case 75:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 74:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 73:
+				SpawnBipship(x, y);
+				lumpneeded[BIP_LUMP]=lumpneeded[BIPSHIP_LUMP]=lumpneeded[BIPSQUISHED_LUMP] = true;
+				break;
+
+			case 78:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 77:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 76:
+				SpawnFlect(x, y);
+				lumpneeded[FLECT_LUMP] = true;
+				break;
+
+			case 81:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 80:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 79:
+				SpawnBlorb(x, y);
+				lumpneeded[BLORB_LUMP] = true;
+				break;
+
+			case 84:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 83:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 82:
+				SpawnCeilick(x, y);
+				lumpneeded[CEILICK_LUMP] = true;
+				break;
+
+			case 87:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 86:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 85:
+				SpawnBlooguard(x, y);
+				lumpneeded[BLOOGUARD_LUMP] = true;
+				break;
+
+			case 88:
+				SpawnGrabbiter(x, y);
+				// no additional lump needed - sprites are in WORLDKEEN_LUMP
+				break;
+
+			case 89:
+				SpawnSatellite(x, y);
+				// no additional lump needed - sprites are in WORLDKEEN_LUMP
+				break;
+
+			// case 90 is not used
+			// cases 91 to 98 are direction arrows
+
+			case 99:
+				SpawnHook(x, y);
+				lumpneeded[HOOK_LUMP] = true;
+				break;
+
+			case 100:
+				SpawnSandwich(x, y);
+				lumpneeded[SANDWICH_LUMP] = true;
+				break;
+
+			case 101:
+				SpawnPasscard(x, y);
+				lumpneeded[PASSCARD_LUMP] = true;
+				break;
+
+			case 104:
+				if (gamestate.difficulty < gd_Hard)
+					break;
+			case 103:
+				if (gamestate.difficulty < gd_Normal)
+					break;
+			case 102:
+				SpawnBabobba(x, y);
+				lumpneeded[BABOBBA_LUMP] = true;
+				break;
+
+			case 105:
+			case 106:
+				SpawnRocket(x, y, info-105);
+				// no additional lump needed - sprites are in WORLDKEEN_LUMP
+				break;
+			}
+		}
+	}
+
+	for (ob = player; ob; ob = ob->next)
+	{
+		if (ob->active != ac_allways)
+			ob->active = ac_no;
+	}
+
+	for (i = 0; i < NUMLUMPS; i++)
+	{
+		if (lumpneeded[i])
+		{
+			for (chunk = lumpstart[i]; chunk <= lumpend[i]; chunk++)
+			{
+				CA_MarkGrChunk(chunk);
+			}
+		}
+	}
+}
+
+//============================================================================
+
+statetype s_keenstun = {KEENSTUNSPR, KEENSTUNSPR, step, false, true, 60, 0, 0, T_Projectile, KeenContact, KeenStandReact, &s_keenstand};
+
+//============================================================================
+
+/*
+===========================
+=
+= FlipBigSwitch
+=
+===========================
+*/
+
+void FlipBigSwitch(objtype *ob, boolean isup)
+{
+	Uint16 x, y;
+	Uint16 far *map;
+	Uint16 top, mid, bot;
+	Uint16 *tileptr;
+	Uint16 tile, tx, ty, xi, yi, offset, anim;
+	Uint16 tiles[6];
+
+	//
+	// handle flipping the switch itself:
+	//
+	if (isup)
+	{
+		ty = ob->tilebottom;
+	}
+	else
+	{
+		ty = ob->tiletop - 2;
+	}
+	tx = ob->tileleft - 1;
+	map = mapsegs[2] + mapbwidthtable[ty+1]/2 + tx + 1;
+	while (*map == 0)
+	{
+		map++;
+		tx++;
+	}
+	map = mapsegs[1] + mapbwidthtable[ty]/2 + tx;
+	tileptr = tiles;
+	for (y = 0; y < 3; y++, map += mapwidth)
+	{
+		for (x = 0; x < 2; tileptr++, x++)
+		{
+			tile = map[x];
+			*tileptr = tile + (Sint8)tinf[tile+MANIM];
+		}
+	}
+	RF_MemToMap(tiles, 1, tx, ty, 2, 3);
+
+	tile = *(mapsegs[2]+mapbwidthtable[ty+1]/2 + tx + 1);
+	x = tile >> 8;
+	y = tile & 0xFF;
+	SD_PlaySound(SND_USESWITCH);
+
+	//
+	// toggle whatever was linked to the switch (at tile x, y):
+	//
+	offset = mapbwidthtable[y]/2 + x;
+	map = mapsegs[2] + offset;
+	tile = *map;
+
+	if (tile >= DIRARROWSTART && tile < DIRARROWEND)
+	{
+		// turn direction arrow:
+		*map = arrowflip[tile-DIRARROWSTART] + DIRARROWSTART;
+	}
+	else
+	{
+		map = mapsegs[1] + offset;
+		tile = *map;
+		switch (tinf[tile+INTILE] & INTILE_TYPEMASK)
+		{
+		case INTILE_NOTHING:	// no special tiles
+			mapsegs[2][offset] ^= PLATFORMBLOCK;
+			break;
+
+		case INTILE_BRIDGE:	// bridge
+			for (yi=y; y+2 > yi; yi++)
+			{
+				map = mapsegs[1] + mapbwidthtable[yi]/2 + x - (yi != y);
+				for (xi = x - (yi != y); xi < mapwidth; xi++)
+				{
+					tile = *map;
+					map++;
+					anim = tinf[tile + MANIM];
+					if (!anim)
+						break;
+					tile += (Sint8)anim;
+					RF_MemToMap(&tile, 1, xi, yi, 1, 1);
+				}
+			}
+			break;
+
+		case INTILE_FORCEFIELD:	// active force field
+			map = mapsegs[1];
+			top = *map;
+			mid = *++map;
+			bot = *++map;
+			map = mapsegs[1] + mapbwidthtable[y+1]/2 + x;
+
+			RF_MemToMap(&top, 1, x, y++, 1, 1);
+			while (tinf[*map+INTILE] == INTILE_DEADLY)
+			{
+				RF_MemToMap(&mid, 1, x, y++, 1, 1);
+				map += mapwidth;
+			}
+			RF_MemToMap(&bot, 1, x, y, 1, 1);
+			break;
+
+		case INTILE_FORCEFIELDEND:	// inactive force field
+			map = mapsegs[1] + 3;
+			top = *map;
+			mid = *++map;
+			bot = *++map;
+			map = mapsegs[1] + mapbwidthtable[y+1]/2 + x;
+
+			RF_MemToMap(&top, 1, x, y++, 1, 1);
+			while (tinf[*map+INTILE] != INTILE_FORCEFIELDEND)
+			{
+				RF_MemToMap(&mid, 1, x, y++, 1, 1);
+				map += mapwidth;
+			}
+			RF_MemToMap(&bot, 1, x, y, 1, 1);
+		}
+	}
+}
+
+//============================================================================
+
+/*
+===========================
+=
+= GotSandwich
+=
+===========================
+*/
+
+void GotSandwich(void)
+{
+	SD_WaitSoundDone();
+	SD_PlaySound(SND_QUESTITEM);
+	CA_UpLevel();	// kinda useless without CA_CacheMarks or CA_SetGrPurge
+	// BUG: haven't made anything purgable here, caching the pic may cause an "out of memory" crash
+	CA_CacheGrChunk(KEENTALK1PIC);
+
+	US_CenterWindow(26, 8);
+	VWB_DrawPic(WindowX+WindowW-48, WindowY, KEENTALK1PIC);
+	WindowW -= 48;
+	PrintY += 12;
+	US_CPrint(
+		"This is the second\n"
+		"biggest sandwich\n"
+		"I ever saw!\n"
+		);
+	VW_UpdateScreen();
+	VW_WaitVBL(30);
+	IN_ClearKeysDown();
+	IN_Ack();
+	CA_DownLevel();
+	gamestate.sandwichstate = 1;
+}
+
+/*
+===========================
+=
+= GotHook
+=
+===========================
+*/
+
+void GotHook(void)
+{
+	SD_WaitSoundDone();
+	SD_PlaySound(SND_QUESTITEM);
+	CA_UpLevel();	// kinda useless without CA_CacheMarks or CA_SetGrPurge
+	// BUG: haven't made anything purgable here, caching the pic may cause an "out of memory" crash
+	CA_CacheGrChunk(KEENTALK1PIC);
+
+	US_CenterWindow(26, 8);
+	VWB_DrawPic(WindowX+WindowW-48, WindowY, KEENTALK1PIC);
+	WindowW -= 48;
+	PrintY += 12;
+	US_CPrint(
+		"Wow! A rope and\n"
+		"grappling hook!\n"
+		"They look useful!\n"
+		);
+	VW_UpdateScreen();
+	VW_WaitVBL(30);
+	IN_ClearKeysDown();
+	IN_Ack();
+	CA_DownLevel();
+	gamestate.hookstate = 1;
+}
+
+/*
+===========================
+=
+= GotPasscard
+=
+===========================
+*/
+
+void GotPasscard(void)
+{
+	SD_WaitSoundDone();
+	SD_PlaySound(SND_QUESTITEM);
+	CA_UpLevel();	// kinda useless without CA_CacheMarks or CA_SetGrPurge
+	// BUG: haven't made anything purgable here, caching the pic may cause an "out of memory" crash
+	CA_CacheGrChunk(KEENTALK1PIC);
+
+	US_CenterWindow(26, 8);
+	VWB_DrawPic(WindowX+WindowW-48, WindowY, KEENTALK1PIC);
+	WindowW -= 48;
+	PrintY += 4;
+	US_CPrint(
+		"What's this? Cool!\n"
+		"A passcard for\n"
+		"the Bloogstar Rocket!\n"
+		"(It can fly through\n"
+		"their force field.)"
+		);
+	VW_UpdateScreen();
+	VW_WaitVBL(30);
+	IN_ClearKeysDown();
+	IN_Ack();
+	CA_DownLevel();
+	gamestate.passcardstate = 1;
+}
diff --git a/16/keen456/KEEN4-6/KEEN6/OBJ/fix_RCK6_v15.pat b/16/keen456/KEEN4-6/KEEN6/OBJ/fix_RCK6_v15.pat
new file mode 100755
index 00000000..9fb9c33d
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN6/OBJ/fix_RCK6_v15.pat
@@ -0,0 +1,3 @@
+%file RCK6E15.exe 109058
+%patch $1C 0 0 0 0
+%end
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/KEEN6C/GFXC_CK6.EQU b/16/keen456/KEEN4-6/KEEN6C/GFXC_CK6.EQU
new file mode 100755
index 00000000..3e71cb77
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN6C/GFXC_CK6.EQU
@@ -0,0 +1,55 @@
+;=====================================
+;
+; Graphics .EQU file for .CK6
+; not IGRAB-ed :)
+;
+;=====================================
+
+;INCLUDE "VERSION.EQU"
+
+;
+; Amount of each data item
+;
+NUMFONT     =	2
+NUMFONTM    =	0
+NUMPICM     =	3
+NUMTILE8    =	108
+NUMTILE8M   =	36
+NUMTILE32   =	0
+NUMTILE32M  =	0
+
+;
+; Amount of each item in episode 6
+;
+NUMPICS     =	34
+NUMSPRITES  =	390
+NUMTILE16   =	2376
+NUMTILE16M  =	2736
+NUMEXTERN   =	8
+
+
+;
+; File offsets for data items
+;
+STRUCTPIC       =	0
+STRUCTPICM      =	1
+STRUCTSPRITE    =	2
+
+STARTFONT       =	3
+STARTFONTM      =	(STARTFONT+NUMFONT)
+STARTPICS       =	(STARTFONTM+NUMFONTM)
+STARTPICM       =	(STARTPICS+NUMPICS)
+STARTSPRITES    =	(STARTPICM+NUMPICM)
+STARTTILE8      =	(STARTSPRITES+NUMSPRITES)
+STARTTILE8M     =	(STARTTILE8+1)
+STARTTILE16     =	(STARTTILE8M+1)
+STARTTILE16M    =	(STARTTILE16+NUMTILE16)
+STARTTILE32     =	(STARTTILE16M+NUMTILE16M)
+STARTTILE32M    =	(STARTTILE32+NUMTILE32)
+STARTEXTERN     =	(STARTTILE32M+NUMTILE32M)
+
+NUMCHUNKS       =	(STARTEXTERN+NUMEXTERN)
+
+;
+; Thank you for using IGRAB!
+;
diff --git a/16/keen456/KEEN4-6/KEEN6C/GFXC_CK6.H b/16/keen456/KEEN4-6/KEEN6C/GFXC_CK6.H
new file mode 100755
index 00000000..d4c64559
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN6C/GFXC_CK6.H
@@ -0,0 +1,667 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+#ifndef __GFX_H__
+#define __GFX_H__
+
+//#include "VERSION.H"
+
+//////////////////////////////////////
+//
+// Graphics .H file for .CK6
+// not IGRAB-ed :)
+//
+//////////////////////////////////////
+
+//
+// Lump creation macros
+//
+
+#define START_LUMP(actualname, dummyname) actualname, dummyname=actualname-1,
+#define END_LUMP(actualname, dummyname) dummyname, actualname=dummyname-1,
+
+//
+// Amount of each data item
+//
+
+//common numbers:
+#define NUMCHUNKS    NUMGRCHUNKS
+#define NUMFONT      2
+#define NUMFONTM     0
+#define NUMPICM      3
+#define NUMTILE8     108	// BUG: only 104 tiles exist in EGAGRAPH!
+#define NUMTILE8M    36		// BUG: only 12 tiles exist in EGAGRAPH!
+#define NUMTILE32    0
+#define NUMTILE32M   0
+
+//episode-specific numbers:
+#define NUMPICS      34
+#define NUMSPRITES   390
+#define NUMTILE16    2376
+#define NUMTILE16M   2736
+#define NUMEXTERNS   8
+
+//
+// File offsets for data items
+//
+#define STRUCTPIC    0
+#define STRUCTPICM   1
+#define STRUCTSPRITE 2
+
+#define STARTFONT    3
+#define STARTFONTM   (STARTFONT+NUMFONT)
+#define STARTPICS    (STARTFONTM+NUMFONTM)
+#define STARTPICM    (STARTPICS+NUMPICS)
+#define STARTSPRITES (STARTPICM+NUMPICM)
+#define STARTTILE8   (STARTSPRITES+NUMSPRITES)
+#define STARTTILE8M  (STARTTILE8+1)
+#define STARTTILE16  (STARTTILE8M+1)
+#define STARTTILE16M (STARTTILE16+NUMTILE16)
+#define STARTTILE32  (STARTTILE16M+NUMTILE16M)
+#define STARTTILE32M (STARTTILE32+NUMTILE32)
+#define STARTEXTERNS (STARTTILE32M+NUMTILE32M)
+
+typedef enum {
+	LASTFONT=STARTPICS-1,
+
+	//
+	// PICS
+	//
+
+	PADDINGPIC,                  // 5 (compensate for the missing Star Wars font to give the other pics the correct chunk numbers)
+
+	H_END1PIC,                   // 6
+	H_END2PIC,                   // 7
+	H_END3PIC,                   // 8
+	H_END4PIC,                   // 9
+	H_END5PIC,                   // 10
+
+	START_LUMP(CONTROLS_LUMP_START, __CONTROLSSTART)
+	CP_MAINMENUPIC,              // 11
+	CP_NEWGAMEMENUPIC,           // 12
+	CP_LOADMENUPIC,              // 13
+	CP_SAVEMENUPIC,              // 14
+	CP_CONFIGMENUPIC,            // 15
+	CP_SOUNDMENUPIC,             // 16
+	CP_MUSICMENUPIC,             // 17
+	CP_KEYBOARDMENUPIC,          // 18
+	CP_KEYMOVEMENTPIC,           // 19
+	CP_KEYBUTTONPIC,             // 20
+	CP_JOYSTICKMENUPIC,          // 21
+	CP_OPTIONSMENUPIC,           // 22
+	CP_PADDLEWARPIC,             // 23
+	CP_QUITPIC,                  // 24
+	CP_JOYSTICKPIC,              // 25
+	CP_MENUSCREENPIC,            // 26
+	END_LUMP(CONTROLS_LUMP_END, __CONTROLSEND)
+
+	H_FLASHARROW1PIC,            // 27
+	H_FLASHARROW2PIC,            // 28
+
+	SW_BACKGROUNDPIC,            // 33
+	TITLEPICPIC,                 // 34
+	KEENTALK1PIC,                // 35
+	KEENTALK2PIC,                // 36
+	KEENCOUNT1PIC,               // 37
+	KEENCOUNT2PIC,               // 38
+	KEENCOUNT3PIC,               // 39
+	KEENCOUNT4PIC,               // 40
+	KEENCOUNT5PIC,               // 41
+	KEENCOUNT6PIC,               // 42
+
+	//
+	// MASKED PICS
+	//
+
+	CP_MENUMASKPICM,             // 43
+	CORDPICM,                    // 44
+	METALPOLEPICM,               // 45
+
+	//
+	// SPRITES
+	//
+
+	START_LUMP(PADDLE_LUMP_START, __PADDLESTART)
+	PADDLESPR,                   // 46
+	BALLSPR,                     // 47
+	BALL1PIXELTOTHERIGHTSPR,     // 48
+	BALL2PIXELSTOTHERIGHTSPR,    // 49
+	BALL3PIXELSTOTHERIGHTSPR,    // 50
+	END_LUMP(PADDLE_LUMP_END, __PADDLEEND)
+
+	DEMOPLAQUESPR,               // 51
+
+	START_LUMP(KEEN_LUMP_START, __KEENSTART)
+	KEENSTANDRSPR,               // 52
+	KEENRUNR1SPR,                // 53
+	KEENRUNR2SPR,                // 54
+	KEENRUNR3SPR,                // 55
+	KEENRUNR4SPR,                // 56
+	KEENJUMPR1SPR,               // 57
+	KEENJUMPR2SPR,               // 58
+	KEENJUMPR3SPR,               // 59
+	KEENSTANDLSPR,               // 60
+	KEENRUNL1SPR,                // 61
+	KEENRUNL2SPR,                // 62
+	KEENRUNL3SPR,                // 63
+	KEENRUNL4SPR,                // 64
+	KEENJUMPL1SPR,               // 65
+	KEENJUMPL2SPR,               // 66
+	KEENJUMPL3SPR,               // 67
+	KEENLOOKUSPR,                // 68
+	KEENWAITR1SPR,               // 69
+	KEENWAITR2SPR,               // 70
+	KEENWAITR3SPR,               // 71
+	KEENSITREAD1SPR,             // 72
+	KEENSITREAD2SPR,             // 73
+	KEENSITREAD3SPR,             // 74
+	KEENSITREAD4SPR,             // 75
+	KEENREAD1SPR,                // 76
+	KEENREAD2SPR,                // 77
+	KEENREAD3SPR,                // 78
+	KEENSTOPREAD1SPR,            // 79
+	KEENSTOPREAD2SPR,            // 80
+	KEENLOOKD1SPR,               // 81
+	KEENLOOKD2SPR,               // 82
+	KEENDIE1SPR,                 // 83
+	KEENDIE2SPR,                 // 84
+	KEENSTUNSPR,                 // 85
+	STUNSTARS1SPR,               // 86
+	STUNSTARS2SPR,               // 87
+	STUNSTARS3SPR,               // 88
+	KEENSHOOTLSPR,               // 89
+	KEENJLSHOOTLSPR,             // 90
+	KEENJSHOOTDSPR,              // 91
+	KEENJSHOOTUSPR,              // 92
+	KEENSHOOTUSPR,               // 93
+	KEENSHOOTRSPR,               // 94
+	KEENJRSHOOTRSPR,             // 95
+	STUN1SPR,                    // 96
+	STUN2SPR,                    // 97
+	STUN3SPR,                    // 98
+	STUN4SPR,                    // 99
+	STUNHIT1SPR,                 // 100
+	STUNHIT2SPR,                 // 101
+	KEENSHINNYR1SPR,             // 102
+	KEENSHINNYR2SPR,             // 103
+	KEENSHINNYR3SPR,             // 104
+	KEENSLIDED1SPR,              // 105
+	KEENSLIDED2SPR,              // 106
+	KEENSLIDED3SPR,              // 107
+	KEENSLIDED4SPR,              // 108
+	KEENSHINNYL1SPR,             // 109
+	KEENSHINNYL2SPR,             // 110
+	KEENSHINNYL3SPR,             // 111
+	KEENPLSHOOTUSPR,             // 112
+	KEENPRSHOOTUSPR,             // 113
+	KEENPRSHOOTDSPR,             // 114
+	KEENPLSHOOTDSPR,             // 115
+	KEENPSHOOTLSPR,              // 116
+	KEENPSHOOTRSPR,              // 117
+	KEENENTER1SPR,               // 118
+	KEENENTER2SPR,               // 119
+	KEENENTER3SPR,               // 120
+	KEENENTER4SPR,               // 121
+	KEENENTER5SPR,               // 122
+	KEENHANGLSPR,                // 123
+	KEENHANGRSPR,                // 124
+	KEENCLIMBEDGEL1SPR,          // 125
+	KEENCLIMBEDGEL2SPR,          // 126
+	KEENCLIMBEDGEL3SPR,          // 127
+	KEENCLIMBEDGEL4SPR,          // 128
+	KEENCLIMBEDGER1SPR,          // 129
+	KEENCLIMBEDGER2SPR,          // 130
+	KEENCLIMBEDGER3SPR,          // 131
+	KEENCLIMBEDGER4SPR,          // 132
+	KEENPOGOR1SPR,               // 133
+	KEENPOGOR2SPR,               // 134
+	KEENPOGOL1SPR,               // 135
+	KEENPOGOL2SPR,               // 136
+	BONUS100UPSPR,               // 137
+	BONUS100SPR,                 // 138
+	BONUS200SPR,                 // 139
+	BONUS500SPR,                 // 140
+	BONUS1000SPR,                // 141
+	BONUS2000SPR,                // 142
+	BONUS5000SPR,                // 143
+	BONUS1UPSPR,                 // 144
+	BONUSCLIPSPR,                // 145
+	VIVASPLASH1SPR,              // 146
+	VIVASPLASH2SPR,              // 147
+	VIVASPLASH3SPR,              // 148
+	VIVASPLASH4SPR,              // 149
+	END_LUMP(KEEN_LUMP_END, __KEENEND)
+
+	START_LUMP(SUGAR1_LUMP_START, __SUGAR1START)
+	SUGAR1ASPR,                  // 150
+	SUGAR1BSPR,                  // 151
+	END_LUMP(SUGAR1_LUMP_END, __SUGAR1END)
+
+	START_LUMP(SUGAR2_LUMP_START, __SUGAR2START)
+	SUGAR2ASPR,                  // 152
+	SUGAR2BSPR,                  // 153
+	END_LUMP(SUGAR2_LUMP_END, __SUGAR2END)
+
+	START_LUMP(SUGAR3_LUMP_START, __SUGAR3START)
+	SUGAR3ASPR,                  // 154
+	SUGAR3BSPR,                  // 155
+	END_LUMP(SUGAR3_LUMP_END, __SUGAR3END)
+
+	START_LUMP(SUGAR4_LUMP_START, __SUGAR4START)
+	SUGAR4ASPR,                  // 156
+	SUGAR4BSPR,                  // 157
+	END_LUMP(SUGAR4_LUMP_END, __SUGAR4END)
+
+	START_LUMP(SUGAR5_LUMP_START, __SUGAR5START)
+	SUGAR5ASPR,                  // 158
+	SUGAR5BSPR,                  // 159
+	END_LUMP(SUGAR5_LUMP_END, __SUGAR5END)
+
+	START_LUMP(SUGAR6_LUMP_START, __SUGAR6START)
+	SUGAR6ASPR,                  // 160
+	SUGAR6BSPR,                  // 161
+	END_LUMP(SUGAR6_LUMP_END, __SUGAR6END)
+
+	START_LUMP(ONEUP_LUMP_START, __ONEUPSTART)
+	ONEUPASPR,                   // 162
+	ONEUPBSPR,                   // 163
+	END_LUMP(ONEUP_LUMP_END, __ONEUPEND)
+
+	START_LUMP(KEYGEM_LUMP_START, __KEYGEMSTART)
+	REDGEM1SPR,                  // 164
+	REDGEM2SPR,                  // 165
+	YELLOWGEM1SPR,               // 166
+	YELLOWGEM2SPR,               // 167
+	BLUEGEM1SPR,                 // 168
+	BLUEGEM2SPR,                 // 169
+	GREENGEM1SPR,                // 170
+	GREENGEM2SPR,                // 171
+	BONUSGEMSPR,                 // 172
+	END_LUMP(KEYGEM_LUMP_END, __KEYGEMEND)
+
+	START_LUMP(AMMO_LUMP_START, __AMMOSTART)
+	STUNCLIP1SPR,                // 173
+	STUNCLIP2SPR,                // 174
+	END_LUMP(AMMO_LUMP_END, __AMMOEND)
+
+	SCOREBOXSPR,                 // 175
+
+	START_LUMP(LASER_LUMP_START, __LASERSTART)
+	LASER1SPR,                   // 176
+	LASER2SPR,                   // 177
+	LASER3SPR,                   // 178
+	LASER4SPR,                   // 179
+	LASERHIT1SPR,                // 180
+	LASERHIT2SPR,                // 181
+	END_LUMP(LASER_LUMP_END, __LASEREND)
+
+	START_LUMP(SANDWICH_LUMP_START, __SANDWICHSTART)
+	SANDWICHSPR,                 // 182
+	END_LUMP(SANDWICH_LUMP_END, __SANDWICHEND)
+
+	START_LUMP(HOOK_LUMP_START, __ROPESTART)
+	HOOKSPR,                     // 183
+	END_LUMP(HOOK_LUMP_END, __ROPEEND)
+
+	START_LUMP(WORLDKEEN_LUMP_START, __WORLDKEENSTART)
+	WORLDKEENL1SPR,              // 184
+	WORLDKEENL2SPR,              // 185
+	WORLDKEENL3SPR,              // 186
+	WORLDKEENR1SPR,              // 187
+	WORLDKEENR2SPR,              // 188
+	WORLDKEENR3SPR,              // 189
+	WORLDKEENU1SPR,              // 190
+	WORLDKEENU2SPR,              // 191
+	WORLDKEENU3SPR,              // 192
+	WORLDKEEND1SPR,              // 193
+	WORLDKEEND2SPR,              // 194
+	WORLDKEEND3SPR,              // 195
+	WORLDKEENDR1SPR,             // 196
+	WORLDKEENDR2SPR,             // 197
+	WORLDKEENDR3SPR,             // 198
+	WORLDKEENDL1SPR,             // 199
+	WORLDKEENDL2SPR,             // 200
+	WORLDKEENDL3SPR,             // 201
+	WORLDKEENUL1SPR,             // 202
+	WORLDKEENUL2SPR,             // 203
+	WORLDKEENUL3SPR,             // 204
+	WORLDKEENUR1SPR,             // 205
+	WORLDKEENUR2SPR,             // 206
+	WORLDKEENUR3SPR,             // 207
+	WORLDKEENWAVE1SPR,           // 208
+	WORLDKEENWAVE2SPR,           // 209
+	ROCKETSPR,                   // 210
+	ROCKETFLY1SPR,               // 211
+	ROCKETFLY2SPR,               // 212
+	SATELLITE1SPR,               // 213
+	SATELLITE2SPR,               // 214
+	SATELLITE3SPR,               // 215
+	SATELLITE4SPR,               // 216
+	GRABBITER1SPR,               // 217
+	GRABBITER2SPR,               // 218
+	GRABBITERSLEEP1SPR,          // 219
+	GRABBITERSLEEP2SPR,          // 220
+	WORLDKEENTRHOW1SPR,          // 221
+	WORLDKEENTRHOW2SPR,          // 222
+	WORLDKEENCLIMB1SPR,          // 223
+	WORLDKEENCLIMB2SPR,          // 224
+	ROPETHROW1SPR,               // 225
+	ROPETHROW2SPR,               // 226
+	WORLDKEENHANGSPR,            // 227
+	FLAGFLIP1SPR,                // 228
+	FLAGFLIP2SPR,                // 229
+	FLAGFLIP3SPR,                // 230
+	FLAGFLIP4SPR,                // 231
+	FLAGFLIP5SPR,                // 232
+	FLAGFALL1SPR,                // 233
+	FLAGFALL2SPR,                // 234
+	FLAGFLAP1SPR,                // 235
+	FLAGFLAP2SPR,                // 236
+	FLAGFLAP3SPR,                // 237
+	FLAGFLAP4SPR,                // 238
+	END_LUMP(WORLDKEEN_LUMP_END, __WORLDKEENEND)
+
+	START_LUMP(FLEEX_LUMP_START, __FLEEXSTART)
+	FLEEXWALKR1SPR,              // 239
+	FLEEXWALKR2SPR,              // 240
+	FLEEXWALKL1SPR,              // 241
+	FLEEXWALKL2SPR,              // 242
+	FLEEXLOOK1SPR,               // 243
+	FLEEXLOOK2SPR,               // 244
+	FLEEXSTUNSPR,             // 245
+	END_LUMP(FLEEX_LUMP_END, __FLEEXEND)
+
+	START_LUMP(CEILICK_LUMP_START, __CEILICKSTART)
+	CEILICK1SPR,                 // 246
+	CEILICK2SPR,                 // 247
+	TONGUE1SPR,                  // 248
+	TONGUE2SPR,                  // 249
+	TONGUE3SPR,                  // 250
+	TONGUE4SPR,                  // 251
+	TONGUE5SPR,                  // 252
+	CEILICKSTUNSPR,           // 253
+	END_LUMP(CEILICK_LUMP_END, __CEILICKEND)
+
+	START_LUMP(BLOOGUARD_LUMP_START, __BLOOGUARDSTART)
+	BLOOGUARDWALKL1SPR,          // 254
+	BLOOGUARDWALKL2SPR,          // 255
+	BLOOGUARDWALKL3SPR,          // 256
+	BLOOGUARDWALKL4SPR,          // 257
+	BLOOGUARDWALKR1SPR,          // 258
+	BLOOGUARDWALKR2SPR,          // 259
+	BLOOGUARDWALKR3SPR,          // 260
+	BLOOGUARDWALKR4SPR,          // 261
+	BLOOGUARDSWINGL1SPR,         // 262
+	BLOOGUARDSWINGL2SPR,         // 263
+	BLOOGUARDSWINGL3SPR,         // 264
+	BLOOGUARDSWINGR1SPR,         // 265
+	BLOOGUARDSWINGR2SPR,         // 266
+	BLOOGUARDSWINGR3SPR,         // 267
+	BLOOGUARDSTUNSPR,         // 268
+	END_LUMP(BLOOGUARD_LUMP_END, __BLOOGUARDEND)
+
+	START_LUMP(BIPSHIP_LUMP_START, __BIPSHIPSTART)
+	BIPSHIPRSPR,                 // 269
+	BIPSHIPRTURN1SPR,            // 270
+	BIPSHIPRTURN2SPR,            // 271
+	BIPSHIPRTURN3SPR,            // 272
+	BIPSHIPRTURN4SPR,            // 273
+	BIPSHIPLSPR,                 // 274
+	BIPSHIPLTURN1SPR,            // 275
+	BIPSHIPLTURN2SPR,            // 276
+	BIPSHIPLTURN3SPR,            // 277
+	BIPSHIPLTURN4SPR,            // 278
+	BIPSHIPEXPLODE1SPR,          // 279
+	BIPSHIPEXPLODE2SPR,          // 280
+	BIPSHIPEXPLODE3SPR,          // 281
+	BIPSHIPEXPLODE4SPR,          // 282
+	BIPSHIPEXPLODE5SPR,          // 283
+	BIPSHIPSHOTSPR,              // 284
+	END_LUMP(BIPSHIP_LUMP_END, __BIPSHIPEND)
+
+	START_LUMP(BABOBBA_LUMP_START, __BABOBBASTART)
+	BABOBBAL1SPR,                // 285
+	BABOBBAL2SPR,                // 286
+	BABOBBAL3SPR,                // 287
+	BABOBBAR1SPR,                // 288
+	BABOBBAR2SPR,                // 289
+	BABOBBAR3SPR,                // 290
+	BABOBBASHOT1SPR,             // 291
+	BABOBBASHOT2SPR,             // 292
+	BABOBBASTUNSPR,           // 293
+	BABOBBASLEEP1SPR,            // 294
+	BABOBBASLEEP2SPR,            // 295
+	BABOBBASLEEP3SPR,            // 296
+	BABOBBASLEEP4SPR,            // 297
+	END_LUMP(BABOBBA_LUMP_END, __BABOBBAEND)
+
+	START_LUMP(NOSPIKE_LUMP_START, __NOSPIKESTART)
+	NOSPIKESTANDSPR,             // 298
+	NOSPIKERUNR1SPR,             // 299
+	NOSPIKERUNR2SPR,             // 300
+	NOSPIKERUNR3SPR,             // 301
+	NOSPIKERUNR4SPR,             // 302
+	NOSPIKERUNL1SPR,             // 303
+	NOSPIKERUNL2SPR,             // 304
+	NOSPIKERUNL3SPR,             // 305
+	NOSPIKERUNL4SPR,             // 306
+	NOSPIKEWALKR1SPR,            // 307
+	NOSPIKEWALKR2SPR,            // 308
+	NOSPIKEWALKR3SPR,            // 309
+	NOSPIKEWALKR4SPR,            // 310
+	NOSPIKEWALKL1SPR,            // 311
+	NOSPIKEWALKL2SPR,            // 312
+	NOSPIKEWALKL3SPR,            // 313
+	NOSPIKEWALKL4SPR,            // 314
+	NOSPIKESTUNSPR,           // 315
+	QUESTIONMARKSPR,             // 316
+	END_LUMP(NOSPIKE_LUMP_END, __NOSPIKEEND)
+
+	START_LUMP(FLECT_LUMP_START, __FLECTSTART)
+	FLECTSTANDSPR,               // 317
+	FLECTSTANDRSPR,              // 318
+	FLECTWALKR1SPR,              // 319
+	FLECTWALKR2SPR,              // 320
+	FLECTWALKR3SPR,              // 321
+	FLECTWALKR4SPR,              // 322
+	FLECTSTANDLSPR,              // 323
+	FLECTWALKL1SPR,              // 324
+	FLECTWALKL2SPR,              // 325
+	FLECTWALKL3SPR,              // 326
+	FLECTWALKL4SPR,              // 327
+	FLECTSTUNSPR,             // 328
+	END_LUMP(FLECT_LUMP_END, __FLECTEND)
+
+	START_LUMP(ORBATRIX_LUMP_START, __ORBATRIXSTART)
+	ORBATRIX1SPR,                // 329
+	ORBATRIX2SPR,                // 330
+	ORBATRIX3SPR,                // 331
+	ORBATRIX4SPR,                // 332
+	ORBATRIXL1SPR,               // 333
+	ORBATRIXL2SPR,               // 334
+	ORBATRIXR1SPR,               // 335
+	ORBATRIXR2SPR,               // 336
+	ORBATRIXSPIN1SPR,            // 337
+	ORBATRIXSPIN2SPR,            // 338
+	ORBATRIXSPIN3SPR,            // 339
+	ORBATRIXSPIN4SPR,            // 340
+	ORBATRIXCURLSPR,             // 341
+	END_LUMP(ORBATRIX_LUMP_END, __ORBATRIXEND)
+
+	START_LUMP(BLOOG_LUMP_START, __BLOOGSTART)
+	BLOOGWALKR1SPR,              // 342
+	BLOOGWALKR2SPR,              // 343
+	BLOOGWALKR3SPR,              // 344
+	BLOOGWALKR4SPR,              // 345
+	BLOOGWALKL1SPR,              // 346
+	BLOOGWALKL2SPR,              // 347
+	BLOOGWALKL3SPR,              // 348
+	BLOOGWALKL4SPR,              // 349
+	BLOOGSTUNSPR,             // 350
+	END_LUMP(BLOOG_LUMP_END, __BLOOGEND)
+
+	START_LUMP(RBLOOGLET_LUMP_START, __RBLOOGLETSTART)
+	RBLOOGLETWALKR1SPR,          // 351
+	RBLOOGLETWALKR2SPR,          // 352
+	RBLOOGLETWALKR3SPR,          // 353
+	RBLOOGLETWALKR4SPR,          // 354
+	RBLOOGLETWALKL1SPR,          // 355
+	RBLOOGLETWALKL2SPR,          // 356
+	RBLOOGLETWALKL3SPR,          // 357
+	RBLOOGLETWALKL4SPR,          // 358
+	RBLOOGLETSTUNSPR,         // 359
+	END_LUMP(RBLOOGLET_LUMP_END, __RBLOOGLETEND)
+
+	START_LUMP(YBLOOGLET_LUMP_START, __YBLOOGLETSTART)
+	YBLOOGLETWALKR1SPR,          // 360
+	YBLOOGLETWALKR2SPR,          // 361
+	YBLOOGLETWALKR3SPR,          // 362
+	YBLOOGLETWALKR4SPR,          // 363
+	YBLOOGLETWALKL1SPR,          // 364
+	YBLOOGLETWALKL2SPR,          // 365
+	YBLOOGLETWALKL3SPR,          // 366
+	YBLOOGLETWALKL4SPR,          // 367
+	YBLOOGLETSTUNSPR,         // 368
+	END_LUMP(YBLOOGLET_LUMP_END, __YBLOOGLETEND)
+
+	START_LUMP(BBLOOGLET_LUMP_START, __BBLOOGLETSTART)
+	BBLOOGLETWALKR1SPR,          // 369
+	BBLOOGLETWALKR2SPR,          // 370
+	BBLOOGLETWALKR3SPR,          // 371
+	BBLOOGLETWALKR4SPR,          // 372
+	BBLOOGLETWALKL1SPR,          // 373
+	BBLOOGLETWALKL2SPR,          // 374
+	BBLOOGLETWALKL3SPR,          // 375
+	BBLOOGLETWALKL4SPR,          // 376
+	BBLOOGLETSTUNSPR,         // 377
+	END_LUMP(BBLOOGLET_LUMP_END, __BBLOOGLETEND)
+
+	START_LUMP(GBLOOGLET_LUMP_START, __GBLOOGLETSTART)
+	GBLOOGLETWALKR1SPR,          // 378
+	GBLOOGLETWALKR2SPR,          // 379
+	GBLOOGLETWALKR3SPR,          // 380
+	GBLOOGLETWALKR4SPR,          // 381
+	GBLOOGLETWALKL1SPR,          // 382
+	GBLOOGLETWALKL2SPR,          // 383
+	GBLOOGLETWALKL3SPR,          // 384
+	GBLOOGLETWALKL4SPR,          // 385
+	GBLOOGLETSTUNSPR,         // 386
+	END_LUMP(GBLOOGLET_LUMP_END, __GBLOOGLETEND)
+
+	START_LUMP(GIK_LUMP_START, __GIKSTART)
+	GIKWALKR1SPR,                // 387
+	GIKWALKR2SPR,                // 388
+	GIKWALKR3SPR,                // 389
+	GIKWALKL1SPR,                // 390
+	GIKWALKL2SPR,                // 391
+	GIKWALKL3SPR,                // 392
+	GIKJUMPLSPR,                 // 393
+	GIKJUMPRSPR,                 // 394
+	GIKSLIDER1SPR,               // 395
+	GIKSLIDER2SPR,               // 396
+	GIKSLIDEL1SPR,               // 397
+	GIKSLIDEL2SPR,               // 398
+	END_LUMP(GIK_LUMP_END, __GIKEND)
+
+	START_LUMP(BLORB_LUMP_START, __BLORBSTART)
+	BLORB1SPR,                   // 399
+	BLORB2SPR,                   // 400
+	BLORB3SPR,                   // 401
+	END_LUMP(BLORB_LUMP_END, __BLORBEND)
+
+	START_LUMP(BOBBA_LUMP_START, __BOBBASTART)
+	BOBBAL1SPR,                  // 402
+	BOBBAL2SPR,                  // 403
+	BOBBAL3SPR,                  // 404
+	BOBBAR1SPR,                  // 405
+	BOBBAR2SPR,                  // 406
+	BOBBAR3SPR,                  // 407
+	BOBBASHOT1SPR,               // 408
+	BOBBASHOT2SPR,               // 409
+	BOBBASHOT3SPR,               // 410
+	BOBBASHOT4SPR,               // 411
+	BOBBASHOT5SPR,               // 412
+	BOBBASHOT6SPR,               // 413
+	END_LUMP(BOBBA_LUMP_END, __BOBBAEND)
+
+	START_LUMP(BIP_LUMP_START, __BIPSTART)
+	BIPSTANDSPR,                 // 414
+	BIPWALKR1SPR,                // 415
+	BIPWALKR2SPR,                // 416
+	BIPWALKR3SPR,                // 417
+	BIPWALKR4SPR,                // 418
+	BIPWALKL1SPR,                // 419
+	BIPWALKL2SPR,                // 420
+	BIPWALKL3SPR,                // 421
+	BIPWALKL4SPR,                // 422
+	END_LUMP(BIP_LUMP_END, __BIPEND)
+
+	START_LUMP(BIPSQUISHED_LUMP_START, __BIPSQUISHEDSTART)
+	BIPSQUISHEDSPR,              // 423
+	END_LUMP(BIPSQUISHED_LUMP_END, __BIPSQUISHEDEND)
+
+	START_LUMP(PLATFORM_LUMP_START, __PLATFORMSTART)
+	PLATFORMSPR,                 // 424
+	PLATBIP1SPR,                 // 425
+	PLATBIP2SPR,                 // 426
+	PLATBIP3SPR,                 // 427
+	PLATBIP4SPR,                 // 428
+	PLATBIP5SPR,                 // 429
+	PLATBIP6SPR,                 // 430
+	PLATBIP7SPR,                 // 431
+	PLATBIP8SPR,                 // 432
+	END_LUMP(PLATFORM_LUMP_END, __PLATFORMEND)
+
+	START_LUMP(MOLLY_LUMP_START, __MOLLYSTART)
+	MOLLY1SPR,                   // 433
+	MOLLY2SPR,                   // 434
+	END_LUMP(MOLLY_LUMP_END, __MOLLYEND)
+
+	START_LUMP(PASSCARD_LUMP_START, __PASSCARDSTART)
+	PASSCARDSPR,                 // 435
+	END_LUMP(PASSCARD_LUMP_END, __PASSCARDEND)
+
+	//
+	// TILES (these don't need names)
+	//
+
+	LASTTILE=STARTEXTERNS-1,
+
+	//
+	// EXTERNS
+	//
+
+	T_ENDART,                    // 5550
+
+	ORDERSCREEN,                 // 5551
+	OUTOFMEM,                    // 5554
+
+	//demos
+	DEMO0,                       // 5555
+	DEMO1,                       // 5556
+	DEMO2,                       // 5557
+	DEMO3,                       // 5558
+	DEMO4,                       // 5559
+
+	NUMGRCHUNKS
+} graphicnums;
+
+#undef START_LUMP
+#undef END_LUMP
+
+#endif //__GFX_H__
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/KEEN6C/ID_ASM.EQU b/16/keen456/KEEN4-6/KEEN6C/ID_ASM.EQU
new file mode 100755
index 00000000..d27d272c
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN6C/ID_ASM.EQU
@@ -0,0 +1,115 @@
+;
+; Equates for all .ASM files
+;
+
+;----------------------------------------------------------------------------
+
+INCLUDE	"GFXC_CK6.EQU"
+
+;----------------------------------------------------------------------------
+
+CGAGR		=	1
+EGAGR		=	2
+VGAGR		=	3
+
+GRMODE		=	CGAGR
+PROFILE		=	0			; 1=keep stats on tile drawing
+
+SC_INDEX	=	03C4h
+SC_RESET	=	0
+SC_CLOCK	=	1
+SC_MAPMASK	=	2
+SC_CHARMAP	=	3
+SC_MEMMODE	=	4
+
+CRTC_INDEX	=	03D4h
+CRTC_H_TOTAL	=	0
+CRTC_H_DISPEND	=	1
+CRTC_H_BLANK	=	2
+CRTC_H_ENDBLANK	=	3
+CRTC_H_RETRACE	=	4
+CRTC_H_ENDRETRACE =	5
+CRTC_V_TOTAL	=	6
+CRTC_OVERFLOW	=	7
+CRTC_ROWSCAN	=	8
+CRTC_MAXSCANLINE =	9
+CRTC_CURSORSTART =	10
+CRTC_CURSOREND	=	11
+CRTC_STARTHIGH	=	12
+CRTC_STARTLOW	=	13
+CRTC_CURSORHIGH	=	14
+CRTC_CURSORLOW	=	15
+CRTC_V_RETRACE	=	16
+CRTC_V_ENDRETRACE =	17
+CRTC_V_DISPEND	=	18
+CRTC_OFFSET	=	19
+CRTC_UNDERLINE	=	20
+CRTC_V_BLANK	=	21
+CRTC_V_ENDBLANK	=	22
+CRTC_MODE	=	23
+CRTC_LINECOMPARE =	24
+
+
+GC_INDEX	=	03CEh
+GC_SETRESET	=	0
+GC_ENABLESETRESET =	1
+GC_COLORCOMPARE	=	2
+GC_DATAROTATE	=	3
+GC_READMAP	=	4
+GC_MODE		=	5
+GC_MISCELLANEOUS =	6
+GC_COLORDONTCARE =	7
+GC_BITMASK	=	8
+
+ATR_INDEX	=	03c0h
+ATR_MODE	=	16
+ATR_OVERSCAN	=	17
+ATR_COLORPLANEENABLE =	18
+ATR_PELPAN	=	19
+ATR_COLORSELECT	=	20
+
+STATUS_REGISTER_1     =	03dah
+
+
+MACRO	WORDOUT
+	out	dx,ax
+ENDM
+
+if 0
+
+MACRO	WORDOUT
+	out	dx,al
+	inc	dx
+	xchg	al,ah
+	out	dx,al
+	dec	dx
+	xchg	al,ah
+ENDM
+
+endif
+
+UPDATEWIDE	=	22
+UPDATEHIGH	=	14
+
+;
+; tile info offsets from segment tinf
+;
+
+ANIM		=	402
+SPEED		=	(ANIM+NUMTILE16)
+
+NORTHWALL	=	(SPEED+NUMTILE16)
+EASTWALL	=	(NORTHWALL+NUMTILE16M)
+SOUTHWALL   =	(EASTWALL+NUMTILE16M)
+WESTWALL    =	(SOUTHWALL+NUMTILE16M)
+MANIM       =	(WESTWALL+NUMTILE16M)
+INTILE      =	(MANIM+NUMTILE16M)
+MSPEED      =	(INTILE+NUMTILE16M)
+
+
+IFE GRMODE-EGAGR
+SCREENWIDTH	=	64
+ENDIF
+IFE GRMODE-CGAGR
+SCREENWIDTH	=	128
+ENDIF
diff --git a/16/keen456/KEEN4-6/KEEN6C/ID_HEADS.H b/16/keen456/KEEN4-6/KEEN6C/ID_HEADS.H
new file mode 100755
index 00000000..d019e5ba
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN6C/ID_HEADS.H
@@ -0,0 +1,109 @@
+/* Reconstructed Commander Keen 4-6 Source Code
+ * Copyright (C) 2021 K1n9_Duk3
+ *
+ * This file is primarily based on:
+ * Catacomb 3-D Source Code
+ * Copyright (C) 1993-2014 Flat Rock Software
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; either version 2 of the License, or
+ * (at your option) any later version.
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License along
+ * with this program; if not, write to the Free Software Foundation, Inc.,
+ * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+ */
+
+// ID_GLOB.H
+
+
+#include <ALLOC.H>
+#include <CTYPE.H>
+#include <DOS.H>
+#include <ERRNO.H>
+#include <FCNTL.H>
+#include <IO.H>
+#include <MEM.H>
+#include <PROCESS.H>
+#include <STDIO.H>
+#include <STDLIB.H>
+#include <STRING.H>
+#include <SYS\STAT.H>
+
+#define __ID_GLOB__
+
+//--------------------------------------------------------------------------
+
+#define KEEN
+#define KEEN6
+
+#define	EXTENSION	"CK6"
+
+extern	char far introscn;
+
+#include "GFXC_CK6.H"
+#include "AUDIOCK6.H"
+
+//--------------------------------------------------------------------------
+
+#define	TEXTGR	0
+#define	CGAGR	1
+#define	EGAGR	2
+#define	VGAGR	3
+
+#define GRMODE	CGAGR
+
+#if GRMODE == EGAGR
+#define GREXT	"EGA"
+#endif
+#if GRMODE == CGAGR
+#define GREXT	"CGA"
+#endif
+
+//#define PROFILE
+
+//
+//	ID Engine
+//	Types.h - Generic types, #defines, etc.
+//	v1.0d1
+//
+
+#ifndef	__TYPES__
+#define	__TYPES__
+
+typedef	enum	{false,true}	boolean;
+typedef	unsigned	char		byte;
+typedef	unsigned	int			word;
+typedef	unsigned	long		longword;
+typedef	byte *					Ptr;
+
+typedef	struct
+		{
+			int	x,y;
+		} Point;
+typedef	struct
+		{
+			Point	ul,lr;
+		} Rect;
+
+#define	nil	((void *)0)
+
+#endif
+
+#include "ID_MM.H"
+#include "ID_CA.H"
+#include "ID_VW.H"
+#include "ID_RF.H"
+#include "ID_IN.H"
+#include "ID_SD.H"
+#include "ID_US.H"
+
+
+void	Quit (char *error);		// defined in user program
+
diff --git a/16/keen456/KEEN4-6/KEEN6C/OBJ/fix_RCK6C_v15.pat b/16/keen456/KEEN4-6/KEEN6C/OBJ/fix_RCK6C_v15.pat
new file mode 100755
index 00000000..272ca2df
--- /dev/null
+++ b/16/keen456/KEEN4-6/KEEN6C/OBJ/fix_RCK6C_v15.pat
@@ -0,0 +1,3 @@
+%file RCK6C15.exe 102166
+%patch $1C 0 0 0 0
+%end
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/RCK4.DSK b/16/keen456/KEEN4-6/RCK4.DSK
new file mode 100755
index 00000000..385701f5
Binary files /dev/null and b/16/keen456/KEEN4-6/RCK4.DSK differ
diff --git a/16/keen456/KEEN4-6/RCK4.PRJ b/16/keen456/KEEN4-6/RCK4.PRJ
new file mode 100755
index 00000000..0bad23e0
Binary files /dev/null and b/16/keen456/KEEN4-6/RCK4.PRJ differ
diff --git a/16/keen456/KEEN4-6/RCK4C.DSK b/16/keen456/KEEN4-6/RCK4C.DSK
new file mode 100755
index 00000000..885d88ec
Binary files /dev/null and b/16/keen456/KEEN4-6/RCK4C.DSK differ
diff --git a/16/keen456/KEEN4-6/RCK4C.PRJ b/16/keen456/KEEN4-6/RCK4C.PRJ
new file mode 100755
index 00000000..eb76ec7c
Binary files /dev/null and b/16/keen456/KEEN4-6/RCK4C.PRJ differ
diff --git a/16/keen456/KEEN4-6/RCK4GT.DSK b/16/keen456/KEEN4-6/RCK4GT.DSK
new file mode 100755
index 00000000..5832d5f6
Binary files /dev/null and b/16/keen456/KEEN4-6/RCK4GT.DSK differ
diff --git a/16/keen456/KEEN4-6/RCK4GT.PRJ b/16/keen456/KEEN4-6/RCK4GT.PRJ
new file mode 100755
index 00000000..9e319fee
Binary files /dev/null and b/16/keen456/KEEN4-6/RCK4GT.PRJ differ
diff --git a/16/keen456/KEEN4-6/RCK5.DSK b/16/keen456/KEEN4-6/RCK5.DSK
new file mode 100755
index 00000000..359c3fe0
Binary files /dev/null and b/16/keen456/KEEN4-6/RCK5.DSK differ
diff --git a/16/keen456/KEEN4-6/RCK5.PRJ b/16/keen456/KEEN4-6/RCK5.PRJ
new file mode 100755
index 00000000..e25c09bc
Binary files /dev/null and b/16/keen456/KEEN4-6/RCK5.PRJ differ
diff --git a/16/keen456/KEEN4-6/RCK5C.DSK b/16/keen456/KEEN4-6/RCK5C.DSK
new file mode 100755
index 00000000..3facc34f
Binary files /dev/null and b/16/keen456/KEEN4-6/RCK5C.DSK differ
diff --git a/16/keen456/KEEN4-6/RCK5C.PRJ b/16/keen456/KEEN4-6/RCK5C.PRJ
new file mode 100755
index 00000000..2750b1ca
Binary files /dev/null and b/16/keen456/KEEN4-6/RCK5C.PRJ differ
diff --git a/16/keen456/KEEN4-6/RCK5GT.DSK b/16/keen456/KEEN4-6/RCK5GT.DSK
new file mode 100755
index 00000000..15491b44
Binary files /dev/null and b/16/keen456/KEEN4-6/RCK5GT.DSK differ
diff --git a/16/keen456/KEEN4-6/RCK5GT.PRJ b/16/keen456/KEEN4-6/RCK5GT.PRJ
new file mode 100755
index 00000000..9090a1c3
Binary files /dev/null and b/16/keen456/KEEN4-6/RCK5GT.PRJ differ
diff --git a/16/keen456/KEEN4-6/RCK6.DSK b/16/keen456/KEEN4-6/RCK6.DSK
new file mode 100755
index 00000000..10074f9b
Binary files /dev/null and b/16/keen456/KEEN4-6/RCK6.DSK differ
diff --git a/16/keen456/KEEN4-6/RCK6.PRJ b/16/keen456/KEEN4-6/RCK6.PRJ
new file mode 100755
index 00000000..089532f9
Binary files /dev/null and b/16/keen456/KEEN4-6/RCK6.PRJ differ
diff --git a/16/keen456/KEEN4-6/RCK6C.DSK b/16/keen456/KEEN4-6/RCK6C.DSK
new file mode 100755
index 00000000..5fa64a36
Binary files /dev/null and b/16/keen456/KEEN4-6/RCK6C.DSK differ
diff --git a/16/keen456/KEEN4-6/RCK6C.PRJ b/16/keen456/KEEN4-6/RCK6C.PRJ
new file mode 100755
index 00000000..984a492d
Binary files /dev/null and b/16/keen456/KEEN4-6/RCK6C.PRJ differ
diff --git a/16/keen456/KEEN4-6/RCK6C15.DSK b/16/keen456/KEEN4-6/RCK6C15.DSK
new file mode 100755
index 00000000..dfa41f4d
Binary files /dev/null and b/16/keen456/KEEN4-6/RCK6C15.DSK differ
diff --git a/16/keen456/KEEN4-6/RCK6C15.PRJ b/16/keen456/KEEN4-6/RCK6C15.PRJ
new file mode 100755
index 00000000..a93509d6
Binary files /dev/null and b/16/keen456/KEEN4-6/RCK6C15.PRJ differ
diff --git a/16/keen456/KEEN4-6/RCK6E15.DSK b/16/keen456/KEEN4-6/RCK6E15.DSK
new file mode 100755
index 00000000..29dc676b
Binary files /dev/null and b/16/keen456/KEEN4-6/RCK6E15.DSK differ
diff --git a/16/keen456/KEEN4-6/RCK6E15.PRJ b/16/keen456/KEEN4-6/RCK6E15.PRJ
new file mode 100755
index 00000000..6c59aee4
Binary files /dev/null and b/16/keen456/KEEN4-6/RCK6E15.PRJ differ
diff --git a/16/keen456/KEEN4-6/static/MAKEOBJ.EXE b/16/keen456/KEEN4-6/static/MAKEOBJ.EXE
new file mode 100755
index 00000000..94fedafb
Binary files /dev/null and b/16/keen456/KEEN4-6/static/MAKEOBJ.EXE differ
diff --git a/16/keen456/KEEN4-6/static/make.bat b/16/keen456/KEEN4-6/static/make.bat
new file mode 100755
index 00000000..2bc31c59
--- /dev/null
+++ b/16/keen456/KEEN4-6/static/make.bat
@@ -0,0 +1,30 @@
+@echo off
+rem bcc makeobj.c
+
+makeobj c AUDIODCT.CK4 ..\keen4\ck4adict.obj _audiodict
+makeobj f AUDIOHED.CK4 ..\keen4\ck4ahead.obj _AudioHeader _audiohead
+makeobj c EGADICT.CK4  ..\keen4\ck4edict.obj _EGAdict
+makeobj f EGAHEAD.CK4  ..\keen4\ck4ehead.obj EGA_grafixheader _EGAhead
+makeobj c CGADICT.CK4  ..\keen4\ck4cdict.obj _CGAdict
+makeobj f CGAHEAD.CK4  ..\keen4\ck4chead.obj CGA_grafixheader _CGAhead
+makeobj f MAPHEAD.CK4  ..\keen4\ck4mhead.obj MapHeader _maphead
+makeobj f introscn.CK4 ..\keen4\ck4intro.obj _introscn
+
+makeobj c AUDIODCT.CK5 ..\keen5\ck5adict.obj _audiodict
+makeobj f AUDIOHED.CK5 ..\keen5\ck5ahead.obj _AudioHeader _audiohead
+makeobj c EGADICT.CK5  ..\keen5\ck5edict.obj _EGAdict
+makeobj f EGAHEAD.CK5  ..\keen5\ck5ehead.obj EGA_grafixheader _EGAhead
+makeobj c CGADICT.CK5  ..\keen5\ck5cdict.obj _CGAdict
+makeobj f CGAHEAD.CK5  ..\keen5\ck5chead.obj CGA_grafixheader _CGAhead
+makeobj f MAPHEAD.CK5  ..\keen5\ck5mhead.obj MapHeader _maphead
+makeobj f introscn.CK5 ..\keen5\ck5intro.obj _introscn
+
+makeobj c AUDIODCT.CK6 ..\keen6\ck6adict.obj _audiodict
+makeobj f AUDIOHED.CK6 ..\keen6\ck6ahead.obj _AudioHeader _audiohead
+makeobj c EGADICT.CK6  ..\keen6\ck6edict.obj _EGAdict
+makeobj f EGAHEAD.CK6  ..\keen6\ck6ehead.obj EGA_grafixheader _EGAhead
+makeobj c CGADICT.CK6  ..\keen6\ck6cdict.obj _CGAdict
+makeobj f CGAHEAD.CK6  ..\keen6\ck6chead.obj CGA_grafixheader _CGAhead
+makeobj f MAPHEAD.CK6  ..\keen6\ck6mhead.obj MapHeader _maphead
+makeobj f introscn.CK6 ..\keen6\ck6intro.obj _introscn
+makeobj f orderscn.CK6 ..\keen6\ck6order.obj _orderscn
diff --git a/16/keen456/KEEN4-6/static/makeobj.c b/16/keen456/KEEN4-6/static/makeobj.c
new file mode 100755
index 00000000..fe85a9d6
--- /dev/null
+++ b/16/keen456/KEEN4-6/static/makeobj.c
@@ -0,0 +1,470 @@
+/*
+** makeobj.c
+**
+**---------------------------------------------------------------------------
+** Copyright 2014 Braden Obrzut
+** All rights reserved.
+**
+** Redistribution and use in source and binary forms, with or without
+** modification, are permitted provided that the following conditions
+** are met:
+**
+** 1. Redistributions of source code must retain the above copyright
+**    notice, this list of conditions and the following disclaimer.
+** 2. Redistributions in binary form must reproduce the above copyright
+**    notice, this list of conditions and the following disclaimer in the
+**    documentation and/or other materials provided with the distribution.
+** 3. The name of the author may not be used to endorse or promote products
+**    derived from this software without specific prior written permission.
+**
+** THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
+** IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
+** OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
+** IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
+** INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
+** NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
+** DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
+** THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
+** (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
+** THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
+**---------------------------------------------------------------------------
+**
+** This is a throwaway program to create OMF object files for DOS. It also
+** extracts the object files.  It should be compatible with MakeOBJ by John
+** Romero except where we calculate the checksum correctly.
+**
+*/
+
+#include <stdio.h>
+#include <malloc.h>
+#include <string.h>
+#include <ctype.h>
+#include <stdlib.h>
+
+#pragma pack(1)
+typedef struct
+{
+	unsigned char type;
+	unsigned short len;
+} SegHeader;
+
+typedef struct
+{
+	unsigned short len;
+	unsigned char name;
+	unsigned char classname;
+	unsigned char overlayname;
+} SegDef;
+#pragma pack()
+
+const char* ReadFile(const char* fn, int *size)
+{
+	char* out;
+
+	FILE* f = fopen(fn, "rb");
+	fseek(f, 0, SEEK_END);
+	*size = ftell(f);
+	out = (char*)malloc(*size);
+	fseek(f, 0, SEEK_SET);
+
+	fread(out, *size, 1, f);
+
+	fclose(f);
+
+	return out;
+}
+
+void WriteFile(const char* fn, const char *data, int size)
+{
+	FILE* f = fopen(fn, "wb");
+	fwrite(data, size, 1, f);
+	fclose(f);
+}
+
+void Extract(const char* infn)
+{
+	const char* in;
+	const char* start;
+	const char* p;
+	char outfn[16];
+	char str[256];
+	char *outdata;
+	int outsize;
+	int insize;
+	SegHeader head;
+
+	outdata = NULL;
+
+	start = in = ReadFile(infn, &insize);
+
+	while(in < start + insize)
+	{
+		head = *(SegHeader*)in;
+
+		switch(head.type)
+		{
+			case 0x80: /* THEADR */
+				memcpy(outfn, in+4, in[3]);
+				outfn[in[3]] = 0;
+				printf("Output: %s\n", outfn);
+				{
+					int i;
+					for(i = 0;i < 16;++i)
+					{
+						if(outfn[i] == ' ')
+							outfn[i] = 0;
+					}
+				}
+				break;
+			case 0x88: /* COMENT */
+				switch(in[3])
+				{
+					case 0:
+						memcpy(str, in+5, head.len-2);
+						str[head.len-3] = 0;
+						printf("Comment: %s\n", str);
+						break;
+					default:
+						printf("Unknown comment type %X @ %x ignored.\n", (unsigned char)in[3], (unsigned int)(in - start));
+						break;
+				}
+				break;
+			case 0x96: /* LNAMES */
+				p = in+3;
+				while(p < in+head.len+2)
+				{
+					memcpy(str, p+1, (unsigned char)*p);
+					str[(unsigned char)*p] = 0;
+					printf("Name: %s\n", str);
+
+					p += (unsigned char)*p+1;
+				}
+				break;
+			case 0x98: /* SEGDEF */
+			{
+				SegDef *sd;
+
+				sd = *(in+3) ? (SegDef*)(in+4) : (SegDef*)(in+7);
+				printf("Segment Length: %d\n", sd->len);
+
+				outdata = (char*)malloc(sd->len);
+				outsize = sd->len;
+				break;
+			}
+			case 0x90: /* PUBDEF */
+				p = in+5;
+				if(in[5] == 0)
+					p += 2;
+				while(p < in+head.len+2)
+				{
+					memcpy(str, p+1, (unsigned char)*p);
+					str[(unsigned char)*p] = 0;
+					printf("Public Name: %s\n", str);
+
+					p += (unsigned char)*p+4;
+				}
+				break;
+			case 0xA0: /* LEDATA */
+				printf("Writing data at %d (%d)\n", *(unsigned short*)(in+4), head.len-4);
+				memcpy(outdata+*(unsigned short*)(in+4), in+6, head.len-4);
+				break;
+			case 0x8A: /* MODEND */
+				/* Ignore */
+				break;
+			default:
+				printf("Unknown header type %X @ %x ignored.\n", head.type, (unsigned int)(in - start));
+				break;
+		}
+
+		in += 3 + head.len;
+	}
+
+	WriteFile(outfn, outdata, outsize);
+
+	free((char*)start);
+	free(outdata);
+}
+
+void CheckSum(char *s, unsigned short len)
+{
+	int sum;
+
+	len += 3;
+
+	sum = 0;
+	while(len > 1)
+	{
+		sum += *(unsigned char*)s;
+		++s;
+		--len;
+	}
+	*s = (unsigned char)(0x100-(sum&0xFF));
+}
+
+void MakeDataObj(const char* infn, const char* outfn, const char* segname, const char* symname, int altmode)
+{
+#define Flush() fwrite(d.buf, d.head.len+3, 1, f)
+	union
+	{
+		char buf[4096];
+		SegHeader head;
+	} d;
+	int i;
+	FILE *f;
+	int insize;
+	const char *in;
+	const char *infn_stripped = strrchr(infn, '/');
+	if(strrchr(infn, '\\') > infn_stripped)
+		infn_stripped = strrchr(infn, '\\');
+	if(infn_stripped == NULL)
+		infn_stripped = infn;
+	else
+		++infn_stripped;
+
+	f = fopen(outfn, "wb");
+
+	in = ReadFile(infn, &insize);
+
+	d.head.type = 0x80;
+	d.head.len = 14;
+	d.buf[3] = 12;
+	if(d.buf[3] > 12)
+		d.buf[3] = 12;
+	sprintf(&d.buf[4], "%-12s", infn_stripped);
+	for(i = 0;i < strlen(infn_stripped) && i < 12;++i)
+		d.buf[4+i] = toupper(d.buf[4+i]);
+	/* CheckSum(d.buf, d.head.len); */
+	d.buf[17] = 0; /* For some reason this one isn't checksummed by MakeOBJ */
+	Flush();
+
+	d.head.type = 0x88;
+	d.head.len = 15;
+	d.buf[3] = 0;
+	d.buf[4] = 0;
+	/* We're not really MakeOBJ v1.1, but to allow us to verify with md5sums */
+	memcpy(&d.buf[5], "MakeOBJ v1.1", 12);
+	CheckSum(d.buf, d.head.len);
+	Flush();
+
+	d.head.type = 0x96;
+	d.head.len = strlen(infn_stripped)+40;
+	d.buf[3] = 6;
+	memcpy(&d.buf[4], "DGROUP", 6);
+	d.buf[10] = 5;
+	memcpy(&d.buf[11], "_DATA", 5);
+	d.buf[16] = 4;
+	memcpy(&d.buf[17], "DATA", 4);
+	d.buf[21] = 0;
+	d.buf[22] = 5;
+	memcpy(&d.buf[23], "_TEXT", 5);
+	d.buf[28] = 4;
+	memcpy(&d.buf[29], "CODE", 4);
+	d.buf[33] = 8;
+	memcpy(&d.buf[34], "FAR_DATA", 8);
+	if(!segname)
+	{
+		if(!altmode)
+		{
+			d.buf[42] = strlen(infn_stripped)-1;
+			for(i = 0;i < strlen(infn_stripped)-4;++i)
+			{
+				if(i == 0)
+					d.buf[43] = toupper(infn_stripped[0]);
+				else
+					d.buf[43+i] = tolower(infn_stripped[i]);
+			}
+			memcpy(&d.buf[43+i], "Seg", 3);
+		}
+		else
+		{
+			d.head.len = 40;
+		}
+	}
+	else
+	{
+		d.head.len = strlen(segname)+41;
+		d.buf[42] = strlen(segname);
+		strcpy(&d.buf[43], segname);
+	}
+	CheckSum(d.buf, d.head.len);
+	Flush();
+
+	d.head.type = 0x98;
+	d.head.len = 7;
+	*(unsigned short*)(d.buf+4) = insize;
+	if(altmode == 0)
+	{
+		d.buf[3] = (char)((unsigned char)0x60);
+		d.buf[6] = 8;
+		d.buf[7] = 7;
+		d.buf[8] = 4;
+	}
+	else
+	{
+		d.buf[3] = (char)((unsigned char)0x48);
+		d.buf[6] = 2;
+		d.buf[7] = 3;
+		d.buf[8] = 4;
+	}
+	CheckSum(d.buf, d.head.len);
+	Flush();
+
+	if(altmode)
+	{
+		d.head.type = 0x9A;
+		d.head.len = 4;
+		d.buf[3] = 1;
+		d.buf[4] = (char)((unsigned char)0xFF);
+		d.buf[5] = 1;
+		CheckSum(d.buf, d.head.len);
+		Flush();
+	}
+
+	d.head.type = 0x90;
+	d.head.len = strlen(infn_stripped)+4;
+	d.buf[3] = 1;
+	d.buf[4] = 1;
+	if(!symname)
+	{
+		d.buf[5] = strlen(infn_stripped)-3;
+		d.buf[6] = '_';
+		for(i = 0;i < strlen(infn_stripped)-4;++i)
+			d.buf[7+i] = tolower(infn_stripped[i]);
+	}
+	else
+	{
+		d.head.len = strlen(symname)+7;
+		d.buf[5] = strlen(symname);
+		strcpy(&d.buf[6], symname);
+		i = strlen(symname)-1;
+	}
+	d.buf[7+i] = 0;
+	d.buf[8+i] = 0;
+	d.buf[9+i] = 0;
+	/* This checksum is calculated wrong in MakeOBJ, although I don't know in what way. */
+	CheckSum(d.buf, d.head.len);
+	Flush();
+
+#define LEDATA_LEN 1024
+	for(i = 0;i < insize;i += LEDATA_LEN)
+	{
+		d.head.type = 0xA0;
+		d.head.len = insize - i > LEDATA_LEN ? LEDATA_LEN+4 : insize - i + 4;
+		d.buf[3] = 1;
+		*(unsigned short*)(d.buf+4) = i;
+		memcpy(&d.buf[6], &in[i], d.head.len-4);
+		CheckSum(d.buf, d.head.len);
+		Flush();
+	}
+
+	d.head.type = 0x8A;
+	d.head.len = 2;
+	d.buf[3] = 0;
+	d.buf[4] = 0;
+	CheckSum(d.buf, d.head.len);
+	Flush();
+
+	fclose(f);
+	free((char*)in);
+}
+
+void DumpData(const char* infn, const char* outfn, int skip)
+{
+	FILE *f;
+	int i;
+	int insize;
+	char symname[9];
+	const char *in;
+	const char *infn_stripped = strrchr(infn, '/');
+	if(strrchr(infn, '\\') > infn_stripped)
+		infn_stripped = strrchr(infn, '\\');
+	if(infn_stripped == NULL)
+		infn_stripped = infn;
+	else
+		++infn_stripped;
+
+	f = fopen(outfn, "wb");
+
+	memset(symname, 0, 9);
+	memcpy(symname, infn_stripped, strlen(infn_stripped)-4);
+	fprintf(f, "char far %s[] ={\r\n", symname);
+
+	in = ReadFile(infn, &insize);
+
+	for(i = skip;i < insize;++i)
+	{
+		fprintf(f, "%d", (unsigned char)in[i]);
+		if(i != insize-1)
+			fprintf(f, ",\r\n");
+	}
+	fprintf(f, " };\r\n");
+
+	fclose(f);
+	free((char*)in);
+}
+
+int main(int argc, char* argv[])
+{
+	if(argc < 3)
+	{
+		printf("Converts file to OMF.\nUseage:\n  ./makeobj [fx] <input> ...\n");
+		return 0;
+	}
+
+	switch(argv[1][0])
+	{
+		case 'c':
+			if(argc < 4)
+			{
+				printf("Need an output location. (Extra parms: <output> [<symbol>])\n");
+				return 0;
+			}
+			else
+			{
+				const char *symname = NULL;
+				if(argc >= 5)
+					symname = argv[4];
+				MakeDataObj(argv[2], argv[3], NULL, symname, 1);
+			}
+			break;
+		default:
+		case 'f':
+			if(argc < 4)
+			{
+				printf("Need an output location. (Extra parms: <output> [<segname> <symbol>])\n");
+				return 0;
+			}
+			else
+			{
+				const char *segname = NULL, *symname = NULL;
+				if(argc >= 6)
+				{
+					segname = argv[4];
+					symname = argv[5];
+				}
+				MakeDataObj(argv[2], argv[3], segname, symname, 0);
+			}
+			break;
+		case 'x':
+			Extract(argv[2]);
+			break;
+		case 's':
+			if(argc < 4)
+			{
+				printf("Need an output location. (Extra parms: <output> [<skip>])\n");
+				return 0;
+			}
+			else
+			{
+				int skip = 0;
+				if(argc >= 5)
+				{
+					skip = atoi(argv[4]);
+				}
+				DumpData(argv[2], argv[3], skip);
+			}
+			break;
+			break;
+	}
+	return 0;
+}
diff --git a/16/keen456/KEEN4-6/static/ripck4.pat b/16/keen456/KEEN4-6/static/ripck4.pat
new file mode 100755
index 00000000..9e2b6752
--- /dev/null
+++ b/16/keen456/KEEN4-6/static/ripck4.pat
@@ -0,0 +1,44 @@
+%ext ck4
+%version 1.4
+
+%dump audiodct.ck4 $354F6 1024
+%dump audiohed.ck4 $20DF0 652
+
+%dump egadict.ck4 $358F6 1024
+%dump egahead.ck4 $21080 14256
+
+%dump introscn.ck4 $1FE40 4008
+
+%dump maphead.ck4 $24830 23406
+
+
+%version cga-1.4
+
+%dump audiodct.ck4 $3335C 1024
+%dump audiohed.ck4 $1E7A0 652
+
+%dump cgadict.ck4 $3375C 1024
+%dump cgahead.ck4 $1EA30 14256
+
+%dump introscn.ck4 $1D7F0 4008
+
+%dump maphead.ck4 $221E0 23406
+
+
+%version 1.4gt	# Note: not supported by CK4PATCH v0.11.3
+
+%dump audiodct.ck4 $359D6 1024
+%dump audiohed.ck4 $212D0 652
+
+%dump egadict.ck4 $35DD6 1024
+%dump egahead.ck4 $21560 14256
+
+%dump introscn.ck4 $20320 4008
+
+%dump maphead.ck4 $24D10 23406
+
+
+%version all
+
+%abort
+%end
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/static/ripck5.pat b/16/keen456/KEEN4-6/static/ripck5.pat
new file mode 100755
index 00000000..cac264c8
--- /dev/null
+++ b/16/keen456/KEEN4-6/static/ripck5.pat
@@ -0,0 +1,44 @@
+%ext ck5
+%version 1.4
+
+%dump audiodct.ck5 $35EC4 1024
+%dump audiohed.ck5 $21C80 828
+
+%dump egadict.ck5 $362C4 1024
+%dump egahead.ck5 $21FC0 14796
+
+%dump introscn.ck5 $20CD0 4008
+
+%dump maphead.ck5 $25990 24090
+
+
+%version cga-1.4
+
+%dump audiodct.ck5 $33B88 1024
+%dump audiohed.ck5 $1F4C0 828
+
+%dump cgadict.ck5 $33F88 1024
+%dump cgahead.ck5 $1F800 14790
+
+%dump introscn.ck5 $1E510 4008
+
+%dump maphead.ck5 $231D0 24090
+
+
+%version 1.4gt	# Note: not supported by CK4PATCH v0.11.3
+
+%dump audiodct.ck5 $36424 1024
+%dump audiohed.ck5 $221E0 828
+
+%dump egadict.ck5 $36824 1024
+%dump egahead.ck5 $22520 14796
+
+%dump introscn.ck5 $21230 4008
+
+%dump maphead.ck5 $25EF0 24090
+
+
+%version all
+
+%abort
+%end
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/static/ripck6.pat b/16/keen456/KEEN4-6/static/ripck6.pat
new file mode 100755
index 00000000..9d5b51d2
--- /dev/null
+++ b/16/keen456/KEEN4-6/static/ripck6.pat
@@ -0,0 +1,65 @@
+%ext ck6
+%version 1.4
+
+%dump audiodct.ck6 $36EEE 1024
+%dump audiohed.ck6 $20C50 760
+
+%dump egadict.ck6 $372EE 1024
+%dump egahead.ck6 $20F50 16683
+
+%dump introscn.ck6 $1FCA0 4008
+
+%dump maphead.ck6 $25080 24306
+
+%dump orderscn.ck6 $2AF80 4008
+
+
+%version 1.5
+
+%dump audiodct.ck6 $36B4E 1024
+%dump audiohed.ck6 $256B0 760
+
+%dump egadict.ck6 $36F4E 1024
+%dump egahead.ck6 $259B0 16683
+
+%dump introscn.ck6 $24700 4008
+
+%dump maphead.ck6 $29AE0 24306
+
+%dump orderscn.ck6 $2F9E0 4008
+
+
+%version cga-1.4
+
+%dump audiodct.ck6 $35030 1024
+%dump audiohed.ck6 $1E830 760
+
+%dump cgadict.ck6 $35430 1024
+%dump cgahead.ck6 $1EB30 16665
+
+%dump introscn.ck6 $1D880 4008
+
+%dump maphead.ck6 $22C50 24306
+
+%dump orderscn.ck6 $28B50 4008
+
+
+%version cga-1.5
+
+%dump audiodct.ck6 $34DA0 1024
+%dump audiohed.ck6 $1E5A0 760
+
+%dump cgadict.ck6 $351A0 1024
+%dump cgahead.ck6 $1E8A0 16665
+
+%dump introscn.ck6 $1D5F0 4008
+
+%dump maphead.ck6 $229C0 24306
+
+%dump orderscn.ck6 $288C0 4008
+
+
+%version all
+
+%abort
+%end
\ No newline at end of file
diff --git a/16/keen456/KEEN4-6/timeline.txt b/16/keen456/KEEN4-6/timeline.txt
new file mode 100755
index 00000000..353fa4d4
--- /dev/null
+++ b/16/keen456/KEEN4-6/timeline.txt
@@ -0,0 +1,352 @@
+KEEN 4 RECREATION TIMELINE:
+---------------------------
+
+2019-02-16:
+
+- started implementation
+- started & finished CK_MAIN.C (except for variables)
+- started & finished CK_DEMO.C (except for variables and fancy intro stuff)
+- started CK_GAME.C, CK_PLAY.C, CK_TEXT.C, CK_STATE.C
+
+
+2019-02-17:
+
+- finished CK_GAME.C (except for variables)
+- finished CK_PLAY.C (except for variables)
+- finished CK_TEXT.C (except for variables)
+- finished CK_STATE.C (except for variables)
+- started CK_KEEN.C
+
+
+2019-02-18:
+
+- finished CK_KEEN.C (except for variables)
+- started & finished CK_KEEN2.C (except for variables)
+- started & finished K4_LEVEL.C (except for variables)
+- started K4_ACT1.C, K4_ACT2.C
+
+
+2019-02-19:
+
+- finished K4_ACT1.C (except for variables)
+- finished K4_ACT2.C (except for variables)
+- started & finished K4_ACT3.C (except for variables)
+- added crawl text in K4_LEVEL.C
+- added states in K4_ACT1.C
+
+
+2019-02-20:
+
+- added states in K4_LEVEL.C
+- added states and initialized variables in CK_KEEN.C
+- added states and initialized variables in CK_KEEN2.C
+- added states in K4_ACT2.C
+- added states in K4_ACT3.C
+
+
+2019-02-22:
+
+- added ID Engine (taken from Catacomb 3D)
+- started creating header files to put it all together
+- fixed tons of typos...
+
+
+2019-02-23:
+
+- finished header files
+- fixed remaining typos & compiler errors
+- code compiles, but linking fails because of missing data that needs to be
+  included in EXE (AUDIOHED, AUDIODICT, EGAHEAD, EGADICT, MAPHEAD)
+- first builds - lots of memory(?) issues, quitting freezes DOSBox
+- fixed menu colors in ID_US_2.C
+- renamed "SKULL 'N' BONES" to "PADDLE WAR" (still need to fix speed issues in pong)
+- fixed error in GFXINFO (wrong number of tile16's) now help texts and quitting work
+- fixed memory issue by increasing number of memory block to 1200 (Cat3D used only 600)
+- first level loads now, but RF_Refresh() locks up/takes forever
+
+
+2019-02-27:
+
+- modified VW_ClearVideo to match Keen4 behavior (also adding in the bug)
+- modified USL_TearDownCtlPanel to use VW_ClearVideo instead of VW_Bar
+- fixed error in DrawCacheBox -> animation plays correctly now
+  (but RF_Refresh still locks up/takes forever)
+- fixed error in ID_CA.H (Keen4 uses tile info order SPEED, ANIM, NORTHWALL, ...)
+  -> RF_Refresh doesn't lock up anymore
+- fixed error in GameLoop -> can now enter sub-levels from world map
+- fixed error in KeenAirReact -> can now land
+- fixed bug in score box (used ammo number for lives)
+- status freezes the game
+- fixed signed/unsigned division bug in KeenStandThink
+- fixed spawn position for slugstain
+- fixed error in PlatformThink (platforms got stuck at the top/right end of the path)
+- added Keen4 Highscore defaults
+- fixed error in StatusWindow -> status window doesn't cause an endless loop anymore
+- fixed error in DrawStatus (bad positions for a few things)
+- fixed bug in CheckGrabPole -> can climb on poles now
+- fixed error in KeenAirReact -> grab edge with correct y position
+- fixed error in KeenClimbEdge1Think -> climbing left works correctly now
+- fixed bugs in SpawnFlag (darn typecasts...)
+- fixed error in ScrollScreenWorld
+- fixed error in KeenPoleTihink -> won't fall off when pressing left/right
+
+
+2019-02-28:
+
+- fixed lindsey floating bug (typecasts)
+- fixed mimrock walking
+- fixed arachnut contact
+- fixed riding the foot
+- fixed thundercloud not randomly turning towards player
+- fixed missing VW_UpdateScreen in LindseyDialog
+- fixed KeenAirReact
+- fixed EggContact
+- fixed controls for scuba keen
+
+
+2019-03-01:
+
+- fixed Sprite, Dopefish and Schoolfish
+- seems fully playable now...
+
+
+2019-03-16:
+
+- renamed PlayDemo to RunDemo, since that's the name that is used in the Keen 4 Demo
+- fixed Dopefish contact code (used to check 'ob' instead of 'hit' for a keenobj)
+
+
+2019-04-10:
+
+- fixed bug in PatchWorldMap (info layer value wasn't set to 0 for completed levels)
+
+
+2019-05-04:
+
+- replaced all sprite numbers with enum names
+- fixed error in WormouthLookLeftThink -> changes state to s_wormouth now
+
+
+2019-05-06:
+
+- replaced some more numbers with enum names
+
+
+2019-05-11:
+
+- fixed error in MergeTile16M
+
+
+2019-05-17:
+
+- fixed bug in WormouthThink (used PIXGLOBAL instead of TILEGLOBAL for xdist)
+
+
+2019-05-19:
+
+- actually moved all far strings into far memory
+
+
+2019-09-27:
+
+- fixed a minor error in PageLayout (skip anything <= space character, not just space char)
+
+
+2019-09-28:
+
+- fixed a bug in control panel (had to adjust indices because options menu was added back in)
+
+
+2019-11-26:
+
+- started implementation of Keen 5 stuff (K5_*.C)
+
+
+2019-11-28:
+
+- started implementation of Keen 6 stuff (K6_*.C)
+
+
+2019-11-30:
+
+- finished implementation of Keen 5 & 6 stuff
+
+
+2019-12-09:
+
+- reorganized KEEN4 project to add support for Keen 5 & 6 without too much redunancy
+- added code specific to Keen 5 and Keen 6 to the main codebase (CK_*.C)
+- excluded code specific to Keen 4 from the other builds (lots of #if & #ifdef)
+- Keen 4 still compiles fine, 5 & 6 still need some header files
+
+
+2019-12-10:
+
+- created header files for Keen 5 and Keen 6
+- all 3 projects compile, but still some bugfixing to do and features to add:
+  - refresh manager constants must be adjusted
+  - copy protection for Keen 6 isn't implemented
+  - sounds for animated tiles (Keen 6) aren't implemented
+- fixed a few bugs, first couple of levels in Keen 6 are playable now
+
+
+2019-12-11:
+
+- adjusted refresh manager constants (now Keen 5 levels are playable, too)
+- adjusted position of the "PRESS A KEY" graphic in the status window 
+  (position in Keen 4 differs from 5 & 6 because of the wetsuit box)
+- added RF_MaskBlockWhite and a few other things
+- studied Terminator-related code in depth, trying to understand it all and
+  find names for all those variables
+
+
+2019-12-12:
+
+- finally found and fixed a bug with the turret shots in Keen 5
+- fixed wrong pole shooting sprites (left and right sprites were swapped)
+- fixed demo-breaking bugs in Spindred and RoboRed (Keen 5)
+- fixed worldmap elevator door code (Keen 5)
+- fixed worldmap rope and rocket bugs (Keen 6)
+- still a demo-breaking bug somewhere (Nospike / Bloogdome, Keen 6 obviously)
+- fixed pole check for shikadi pole sparks
+
+
+2019-12-15:
+
+- FUCLING FINALLY found and fixed the demo-breaking bug in Keen 6
+  (was in NospikeRunThink)
+- fixed bug in Shikadi Master spawn (y offset used tile units instead of pixels)
+- started implementation of the Terminator intro and the Star Wars text crawl
+
+
+2019-12-16:
+
+- finished implementation of the Terminator and Star Wars stuff, but now the
+  compiler crashes...
+- found and fixed the issue that crashed the compiler
+- fixed all bugs in the Staw Wars text crawl
+- fixed all bugs in the Terminator intro
+
+2019-12-17:
+
+- added tile animation sounds for Keen 6
+
+
+2019-12-19:
+
+- implemented Keen 4-6 version of VW_SetScreen (in _ID_VW_AE.ASM) and my
+  customized version of the routine (in ID_VW_AE.ASM). swap the files if you
+  want to use the original code
+- added support for the NOPAN parameter
+- added US_CheckArg in ID_US_1.C
+- added Quiet AdLib mode
+- added Gravis Gamepad support
+
+
+2019-12-20:
+
+- fixed CheckHighScore bug (each episode uses a different map number)
+- fixed shockshund bugs (blast direction, stun jump)
+
+
+2019-12-21:
+
+- fixed EagleWalkThink (condition for starting to fly, Keen 4 obviously)
+- fixed tile-based item stealing for TreasureEater (Keen 4)
+- fixed force field toggling (Keen 6)
+
+
+2019-12-22:
+
+- fixed bug in EagleFlyReact (Keen 4)
+- changed ConfigVersion in ID_US_1.C for full compatibility with version 1.4
+  (saved games are still incompatible, though)
+
+
+2020-01-05:
+
+- modified PaddleWar code to match the code from Keen 4-6
+
+
+2020-01-06:
+
+- moved minimum memory requirement into the episode headers
+  (Keen 4 & 5 need 310,000 bytes, Keen 6 needs 300,000 bytes)
+- added missing code in SD_Default() (also marked the bug in there)
+
+
+2020-01-08:
+
+- fixed a minor issue in ID_RF.C related to the tile animation sounds in Keen 6
+
+
+2020-02-21:
+
+- fixed a bug in Bipship movement code (Keen 6)
+- modified sound engine to avoid SDL_Delay entirely and read port 0x388 instead
+  (which is exactly how version 1.4 and above work)
+
+
+2020-03-05:
+
+- fixed bug in Ampton walk code
+
+
+2020-04-24:
+
+- added the title screen in DemoLoop() (after high scores)
+- replaced some chunk numbers with their enum names in K4_LEVEL.C (smoke sprites)
+
+
+2020-05-20:
+
+- SpawnEnemyShot now makes the object removable (KEEN5)
+
+
+2021-05-05:
+
+- fixed bug in PageLayout (negative top row index)
+
+
+2021-05-05:
+
+- fixed bug in JanitorDialog (bad picture position for KEENMADPIC)
+
+
+2021-06-06 to 2021-06-23:
+
+- renamed things in Keen 4 & 5 to what is believed to be the original naming
+  scheme - Keen 6 stuff is still guesswork
+- adapted code to make it compile with Borland C++ 2.0 and 3.0
+- adjusted compiler settings and code to recreate the original executables as
+  closely as possible (for automated comparison and verification)
+- found and fixed a few bugs along the way
+
+
+2021-06-24:
+
+- tracked down and fixed any remaining differences
+- compiling (with source debugging enabled) and then compressing the EXE files
+  with LZEXE Version 0.91 creates EXACTLY the same files as the original v1.4
+  releases shipped with
+- Mission accomplished, I guess...
+
+
+2021-07-01:
+
+- first public release of this source code
+
+
+2021-07-03:
+
+- Keen 6 EGA v1.5 can now be recreated with this source code thanks to NY00123
+- added some more comments to the source code, mostly explaining what the temp
+  variables are used for in each actor's code
+- changed the function names in the Keen 6 code from ...Think, ...Contact and
+  ...React to T_..., C_... and R_... for more consistency with the Keen 4 and
+  Keen 5 code, also changed some state and sprite names for more consistency
+
+2021-07-08:
+- all CGA executables of versions 1.4 and 1.5 can now be recreated with this
+  source code
+- added a few more comments
diff --git a/16/keen456/LZEXE.EXE b/16/keen456/LZEXE.EXE
new file mode 100755
index 00000000..727c2037
Binary files /dev/null and b/16/keen456/LZEXE.EXE differ
diff --git a/16/keen456/RCK4.BAT b/16/keen456/RCK4.BAT
new file mode 100755
index 00000000..dbb8217c
--- /dev/null
+++ b/16/keen456/RCK4.BAT
@@ -0,0 +1,4 @@
+SET PATH=%PATH%;C:\BC30\BIN
+cd KEEN4-6
+BC RCK4.PRJ
+cd ..
\ No newline at end of file
diff --git a/16/keen456/RCK4C.BAT b/16/keen456/RCK4C.BAT
new file mode 100755
index 00000000..c0b4664a
--- /dev/null
+++ b/16/keen456/RCK4C.BAT
@@ -0,0 +1,4 @@
+SET PATH=%PATH%;C:\BC30\BIN
+cd KEEN4-6
+BC RCK4C.PRJ
+cd ..
\ No newline at end of file
diff --git a/16/keen456/RCK4GT.BAT b/16/keen456/RCK4GT.BAT
new file mode 100755
index 00000000..a34d6ac7
--- /dev/null
+++ b/16/keen456/RCK4GT.BAT
@@ -0,0 +1,4 @@
+SET PATH=%PATH%;C:\BC31\BIN
+cd KEEN4-6
+BC RCK4GT.PRJ
+cd ..
\ No newline at end of file
diff --git a/16/keen456/RCK5.BAT b/16/keen456/RCK5.BAT
new file mode 100755
index 00000000..24f70e18
--- /dev/null
+++ b/16/keen456/RCK5.BAT
@@ -0,0 +1,4 @@
+SET PATH=%PATH%;C:\BC30\BIN
+cd KEEN4-6
+BC RCK5.PRJ
+cd ..
\ No newline at end of file
diff --git a/16/keen456/RCK5C.BAT b/16/keen456/RCK5C.BAT
new file mode 100755
index 00000000..e794cb99
--- /dev/null
+++ b/16/keen456/RCK5C.BAT
@@ -0,0 +1,4 @@
+SET PATH=%PATH%;C:\BC30\BIN
+cd KEEN4-6
+BC RCK5C.PRJ
+cd ..
\ No newline at end of file
diff --git a/16/keen456/RCK5GT.BAT b/16/keen456/RCK5GT.BAT
new file mode 100755
index 00000000..37c160fa
--- /dev/null
+++ b/16/keen456/RCK5GT.BAT
@@ -0,0 +1,4 @@
+SET PATH=%PATH%;C:\BC31\BIN
+cd KEEN4-6
+BC RCK5GT.PRJ
+cd ..
\ No newline at end of file
diff --git a/16/keen456/RCK6.BAT b/16/keen456/RCK6.BAT
new file mode 100755
index 00000000..1f044658
--- /dev/null
+++ b/16/keen456/RCK6.BAT
@@ -0,0 +1,4 @@
+SET PATH=%PATH%;C:\BC30\BIN
+cd KEEN4-6
+BC RCK6.PRJ
+cd ..
\ No newline at end of file
diff --git a/16/keen456/RCK6C.BAT b/16/keen456/RCK6C.BAT
new file mode 100755
index 00000000..31a281d6
--- /dev/null
+++ b/16/keen456/RCK6C.BAT
@@ -0,0 +1,4 @@
+SET PATH=%PATH%;C:\BC30\BIN
+cd KEEN4-6
+BC RCK6C.PRJ
+cd ..
\ No newline at end of file
diff --git a/16/keen456/RCK6C15.BAT b/16/keen456/RCK6C15.BAT
new file mode 100755
index 00000000..5ad44a37
--- /dev/null
+++ b/16/keen456/RCK6C15.BAT
@@ -0,0 +1,4 @@
+SET PATH=%PATH%;C:\BC31\BIN
+cd KEEN4-6
+BC RCK6C15.PRJ
+cd ..
\ No newline at end of file
diff --git a/16/keen456/RCK6E15.BAT b/16/keen456/RCK6E15.BAT
new file mode 100755
index 00000000..50a3bb49
--- /dev/null
+++ b/16/keen456/RCK6E15.BAT
@@ -0,0 +1,4 @@
+SET PATH=%PATH%;C:\BC31\BIN
+cd KEEN4-6
+BC RCK6E15.PRJ
+cd ..
\ No newline at end of file
diff --git a/16/keen456/cleanup.bat b/16/keen456/cleanup.bat
new file mode 100755
index 00000000..dbf734f0
--- /dev/null
+++ b/16/keen456/cleanup.bat
@@ -0,0 +1,7 @@
+@echo off
+del KEEN4-6\KEEN4\OBJ\*.obj
+del KEEN4-6\KEEN4C\OBJ\*.obj
+del KEEN4-6\KEEN5\OBJ\*.obj
+del KEEN4-6\KEEN5C\OBJ\*.obj
+del KEEN4-6\KEEN6\OBJ\*.obj
+del KEEN4-6\KEEN6C\OBJ\*.obj
\ No newline at end of file
diff --git a/16/keen456/readme.txt b/16/keen456/readme.txt
new file mode 100755
index 00000000..b8aeb87a
--- /dev/null
+++ b/16/keen456/readme.txt
@@ -0,0 +1,376 @@
+Reconstructed Commander Keen 4-6 Source Code
+Copyright (C) 2021 K1n9_Duk3
+===============================================================================
+
+This is an UNOFFICIAL reconstruction of the original Keen 4-6 source code. More
+specifically, it is a reconstruction of the version 1.4 (and 1.5) EGA and CGA
+releases.
+
+The code is primarily based on the Catacomb 3-D source code (ID Engine files).
+The text view code (CK_TEXT.C) is based on Wolfenstein 3-D, and the main game
+and actor code is loosely based on Keen Dreams.
+
+Catacomb 3-D Source Code
+Copyright (C) 1993-2014 Flat Rock Software
+
+Wolfenstein 3-D Source Code
+Copyright (C) 1992 id Software
+
+Keen Dreams Source Code
+Copyright (C) 2014 Javier M. Chavez
+
+This program is free software; you can redistribute it and/or modify
+it under the terms of the GNU General Public License as published by
+the Free Software Foundation; either version 2 of the License, or
+(at your option) any later version.
+
+This program is distributed in the hope that it will be useful,
+but WITHOUT ANY WARRANTY; without even the implied warranty of
+MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+GNU General Public License for more details.
+
+You should have received a copy of the GNU General Public License along
+with this program; if not, write to the Free Software Foundation, Inc.,
+51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
+
+
+Getting this code to compile
+============================
+
+You will need Borland C++ 2.0, 3.0 or 3.1 to compile this code. Newer versions
+may work, but have not been tested.
+
+In addition to the compiler and this source code, you will also need to extract
+some data files from the original executables. I have provided patch scripts to
+extract that data from the original executables. To use these patch scripts,
+you will need one of the following tools:
+
+CKPatch v0.11.3 (unofficial) - 16 bit DOS application
+http://ny.duke4.net/files.html
+
+K1n9_Duk3's Patching Utility v2.3 - Win32 application
+http://k1n9duk3.shikadi.net/patcher.html
+
+Copy the patching programs into the "static" subdirectory, along with copies of
+the original Keen 4-6 executables. The Keen 4-6 executables should be named
+KEEN4*.EXE, KEEN5*.EXE and KEEN6*.EXE respectively, otherwise the patching
+programs might have trouble recognizing the files.
+
+If you are going to use CKPatch, you should only copy one KEEN4*.EXE file, one
+KEEN5*.EXE and one KEEN6*.EXE file into the "static" directory. CKPatch will
+always use the first file matching this pattern, so if you have both KEEN4C.EXE
+and KEEN4E.EXE in that directory, for example, CK4PATCH will always operate on
+KEEN4C.EXE and ignore KEEN4E.EXE.
+
+These patches will only work on very specific versions of the original game's
+executables (v1.4/v1.5 CGA/EGA). The GT versions are not supported by CKPatch,
+so you will need K1n9_Duk3's Patching Utility to extract their data with the
+patch scripts included in the "static" directory. CKPatch may also be unable to
+open the FormGen release of Keen 4 (and Keen 5, if it exists). Decompressing
+the game's executable with UNLZEXE may fix that problem.
+
+If you are using K1n9_Duk3's Patching Utility, simply run it and open the patch
+file (*.PAT) you want to use. If K1n9_Duk3's Patching Utility found more than
+one supported version of the executables (or none at all), it will ask you to
+open the executable manually. Save the extracted files into the "static"
+directory using the suggested file names.
+
+If you are going to use CKPatch, just copy the files as described above, then
+use the provided batch files as described in the following section.
+
+
+Setting up a working environment in DOSBox
+------------------------------------------
+
+The Borland C++ compilers, as well as CKPATCH, MAKEOBJ and LZEXE, are all DOS
+programs, so you will need a system that is capable of running DOS programs or
+you will have to use an emulator like DOSBox to run these programs.
+
+If you are going to use DOSBox, start out by preparing a base directory on your
+system that you are going to mount as drive C: in DOSBox (mounting your real C:
+drive as C: in DOSBox is NOT recommended). Let's assume your base directory is
+"C:\BASE". Extract the contents of this package into that directory. Also copy
+the Borland C++ compiler(s) you are going to use into that directory,
+preferably into subdirectories named "BC20", "BC30" and "BC31" to make things
+easier for you. You can use different names, but then you will have to edit a
+couple of files and settings later on.
+
+You could just start DOSBox and manually mount your base directory as the C:
+drive in DOSBox, but this project comes with a couple of batch files that make
+the process much easier, as long as things are set up correctly.
+
+In case you didn't know, dragging and dropping a file onto DOSBox.exe will
+start DOSBox and mount the directory in which that file is located in as the C:
+drive in DOSBox, then it will try to execute that file in DOSBox.
+
+At this point, your base directory should have the following contents:
+
+	BC20         - Borland C++ 2.0
+	BC30         - Borland C++ 3.0
+	BC31         - Borland C++ 3.1
+	KEEN4-6      - main source directory
+
+	lzexe.exe    - for compressing executables
+	rck4.bat     - opens RCK4.PRJ with the correct compiler version
+	rck4c.bat    - opens RCK4C.PRJ with the correct compiler version
+	rck5.bat     - opens RCK5.PRJ with the correct compiler version
+	rck5c.bat    - opens RCK5C.PRJ with the correct compiler version
+	rck6.bat     - opens RCK6.PRJ with the correct compiler version
+	rck6c.bat    - opens RCK6C.PRJ with the correct compiler version
+	rck4gt.bat   - opens RCK4GT.PRJ with the correct compiler version
+	rck5gt.bat   - opens RCK5GT.PRJ with the correct compiler version
+	rck6e15.bat  - opens RCK6E15.PRJ with the correct compiler version
+	rck6c15.bat  - opens RCK6C15.PRJ with the correct compiler version
+	ripnmake.bat - extracts data files and converts them into .OBJ files
+	readme.txt   - this file
+
+The first order of business is to drag and drop RIPNMAKE.BAT onto DOSBox.exe or
+onto a shortcut to DOSBox.exe. This will try to extract the required data files
+from the original executables via CKPatch and then convert the data files into
+.OBJ files that the compiler can include when generating the new executables.
+The .OBJ files will be created in the KEEN4, KEEN5 and KEEN6 subdirectories.
+
+Note that you should do this step even if you already extracted the data files
+using K1n9_Duk3's Patching Utility. The RIPNMAKE.BAT file may not be able to
+run the CKPatch programs in that case, but as long as the extracted data files
+are present in the "KEEN4-6\static" directory, it will still convert them into
+.OBJ files and place the .OBJ files into the correct directories.
+
+If you are using CKPatch and you want to extract the data for both the EGA and
+the CGA versions, you need to delete the KEEN*.EXE files from the "static"
+directory after running RIPNMAKE.BAT and then copy the other executables into
+that directory and run RIPNMAKE.BAT again.
+
+
+Check the KEEN4, KEEN5 and KEEN6 directories and make sure the following files
+are in them:
+
+	CK?ADICT.OBJ
+	CK?AHEAD.OBJ
+	CK?CDICT.OBJ (for the CGA version)
+	CK?CHEAD.OBJ (for the CGA version)
+	CK?EDICT.OBJ (for the EGA version)
+	CK?EHEAD.OBJ (for the EGA version)
+	CK?INTRO.OBJ
+	CK?MHEAD.OBJ
+	CK6ORDER.OBJ (only for Keen 6)
+
+You can exit from DOSBox after this is done. Simply type "exit" at the prompt
+and hit Enter.
+
+
+Compiling the code:
+-------------------
+
+The other batch files in your base directory (RCK*.BAT) are provided to make
+compiling the code easy. Simply drag and drop the batch file onto DOSBox.exe
+(or onto a shortcut to DOSBox.exe) and it will open the respective project in
+the correct version of the compiler.
+
+	RCK4       - EGA version 1.4 - Apogee and FormGen release
+	RCK5       - EGA version 1.4 - Apogee (and FormGen?) release)
+	RCK6       - EGA version 1.4 - FormGen release
+	RCK4C      - CGA version 1.4 - Apogee and FormGen release
+	RCK5C      - CGA version 1.4 - Apogee (and FormGen?) release)
+	RCK6C      - CGA version 1.4 - FormGen release
+
+	RCK4GT     - EGA version 1.4 - GT release
+	RCK5GT     - EGA version 1.4 - GT release
+	RCK6E15    - EGA version 1.5 - FormGen release
+	RCK6C15    - CGA version 1.5 - FormGen release
+
+The first six are set up for use with Borland C++ 3.0 by default, the later
+four are set up for use with Borland C++ 3.1. If you want to compile them with
+a different version of the compiler, edit the batch file and change the
+compiler directory (in the "SET PATH=" line) to the one you wish to use. Then
+open the project (drag and drop the batch file onto DOSBox.exe) and then select
+"Options" -> "Directories" from the main menu. Make sure that the Include and
+Library directory settings point to a version that you actually have installed.
+
+Note that RCK4, RCK4C, RCK5, RCK5C, RCK6 and RCK6C are set up to compile with
+BC30, but using the Library directory from BC20. This is required for
+recreating the original executables, but if you don't have both of these
+versions and you don't care about creating 100% identical copies, you can just
+change the directory settings to point to the compiler you have.
+
+To actually compile the code, press F9 or select "Compile" -> "Make" from the
+menu.
+
+Compiling all of the files may take a while, depending on your CPU cycles
+settings in DOSBox. By default, DOSBox should automatically switch to maximum
+cycles mode when Borland C++ 3.0 or 3.1 are started, but not when Borland C++
+2.0 is started. You can simply enter the command "cycles max" at the DOSBox
+prompt (or add it to the batch files) to switch DOSBox into maximum cycles mode
+if the automatic switch doesn't work for you.
+
+With the current code base, it is completely normal to get 3 or 4 warnings as
+the code is compiled. One may come from CK_KEEN2.C ("Condition is always true")
+when compiling Keen 6 v1.5. The other three of them should come from ID_US_1.C
+(2x "Condition is always true" and 1x "Unreachable code"). You can ignore these
+warnings.
+
+Once the code has been compiled, simply press ALT+X or select "File" -> "Quit"
+from the menu. Don't just close DOSBox while Borland C++ is still running, you
+would just end up with lots of useless swap files in your project directory.
+
+Type "exit" at the DOS prompt to quit DOSBox.
+
+Please note that you should always quit DOSBox after compiling a project.
+Trying to compile a second project after the first one may cause issues with
+the provided batch files and the way they adjust the PATH environment variable.
+For example, DOSBox may end up starting the wrong version of the compiler.
+
+
+Recreating the original executables
+===================================
+
+Here's the TL;DR for advanced users:
+
+RCK4.PRJ, RCK5.PRJ, RCK6.PRJ, RCK4C.PRJ, RCK5C.PRJ, RCK6C.PRJ:
+- Use same compiler settings as in the provided RCK?.PRJ files
+- Use LIB directory from Borland C++ 2.0
+- Use INCLUDE directory from Borland C++ 3.0
+- Compile with Borland C++ 3.0
+- Compress compiled EXE file with LZEXE version 0.91
+
+RCK4GT.PJR, RCK5GT.PRJ, RCK6E15.PRJ, RCK6C15.PRJ:
+- Use same compiler settings as in the provided RCK?GT.PRJ/RCK6?15.PRJ files
+- Use LIB and INCLUDE directories from Borland C++ 3.1
+- Compile with Borland C++ 3.1
+- Compress compiled EXE file with LZEXE version 0.91
+
+To create 100% identical copies of the original v1.4 EGA executables, you will
+need a copy of Borland C++ 3.0 as well as a copy of Borland C++ 2.0 (or at
+least the LIB directory from Borland C++ 2.0).
+
+Make sure to start with the original project files included in this package.
+Those have all of the compiler options set to the correct values. Different
+settings may produce slightly different code and the whole point of this is
+to get code that's 100% identical to the original executables.
+
+Unlike Borland C++ 3.1, version 3.0 will not recompile every file when you
+select "Build all" from the "Compile" menu if neither that file nor the header
+files used by that file have changed since the last time that file was
+compiled. Therefore I recommend that you delete all *.OBJ files from the
+"KEEN*\OBJ" directory to make sure everything gets recompiled. The CLEANUP.BAT
+file will take care of that (can be run in Windows as well as in DOSBox).
+
+Open the project in BC30 and select "Options" -> "Directories" from the menu.
+Change the "Include Directories" path to the INCLUDE directory from BC30 and
+change the "Library Directories" path to the LIB directory from BC20.
+
+Compile the code (select either "Make" or "Build all" from the "Compile" menu)
+and once the compiler is done, quit to DOS(Box) and compress the new executable
+with LZEXE. To compress RCK4.EXE, you must type "LZEXE RCK4.EXE" and hit Enter.
+The program will display a message in French about additional information at
+the end of the executable that will be lost after compression and ask if you
+want to abort. Type "N" and hit Enter to compress the file.
+
+
+For reference, these are the results you should be getting after compression:
+
+Keen 4 EGA version 1.4 (Apogee)  : size = 105108 bytes, CRC = 6646B983
+Keen 4 EGA version 1.4 (FormGen) : size = 105140 bytes, CRC = F91E558B
+Keen 4 EGA version 1.4 (GT)      : size = 106178 bytes, CRC = 0A05442E
+Keen 4 CGA version 1.4 (Apogee)  : size =  98007 bytes, CRC = F544DD41
+Keen 4 CGA version 1.4 (FormGen) : size =  98007 bytes, CRC = 018FA365
+
+Keen 5 EGA version 1.4 (Apogee)  : size = 106417 bytes, CRC = 2A45589A
+(No FormGen release of Keen 5 EGA version 1.4 is known at this time.)
+Keen 5 EGA version 1.4 (GT)      : size = 107611 bytes, CRC = 5E450B12
+Keen 5 CGA version 1.4 (Apogee)  : size =  98880 bytes, CRC = FB9EB429
+(No FormGen release of Keen 5 CGA version 1.4 is known at this time.)
+
+Keen 6 EGA version 1.4 (FormGen) : size = 107719 bytes, CRC = 9CDACDAE
+Keen 6 EGA version 1.5 (FormGen) : size = 109058 bytes, CRC = 5B828EE2
+Keen 6 CGA version 1.4 (FormGen) : size = 100964 bytes, CRC = F36A4C51
+Keen 6 CGA version 1.5 (FormGen) : size = 102166 bytes, CRC = D2F379B8
+
+The GT versions appear to have been compiled with Borland C++ 3.1 and its LIB
+directory, but otherwise using the same compiler and optimization settings as
+in the earlier Apogee/FormGen versions.
+
+The only difference between the Apogee/FormGen and the GT versions of the Keen
+4 and 5 executables (obvious differences in the included OBJ files aside) is
+that the GT version has only four entries in the help menu instead of five
+(the Order Info section has been removed) and that the GT version has a
+different set of default high scores. You must have GOODTIMES defined to
+compile these versions (already set in the RCK?GT.PRJ files).
+
+Keen 6 EGA/CGA version 1.5 was also compiled with Borland C++ 3.1 and its LIB
+directory, but it uses completely different compiler and optimization settings
+and also has one new variable in CK_PLAY.C that is never used but still has to
+be present to recreate the original code. It appears that somebody just pressed
+the "Fastest code" button in the compiler optimizations window before version
+1.5 was compiled, which was a bad idea for this code. None of the variables in
+the ID Engine are marked as "volatile", not even the ones that may be changed
+by an interrupt. That means the optimizations may end up generating code that
+leads to endless loops, as is the case with the "while (!LastScan);" loop in
+the PicturePause() routine.
+
+To recreate the exact same files as the original Keen 6 v1.5 executables, you
+need to compress the generated executables with LZEXE and then hex-edit the
+compressed files to replace the "LZ91" signature at offset 0x1C in the EXE file
+with four 0 bytes. If you don't have a hex editor, you can use K1n9_Duk3's
+Patching Utility for that step. Simply open the "fix_RCK6_v15.pat" or the
+"fix_RCK6C_v15.pat" patch file (located in the KEEN4-6\KEEN6\OBJ and
+KEEN4-6\KEEN6C\OBJ directories, respectively) with K1n9_Duk3's Patching Utility
+and let it patch the compressed executable for you.
+
+
+Borland C++ 2.0 issues?
+=======================
+
+Any versions of Keen 4-6 prior to version 1.4 appear to have been compiled with
+Borland C++ 2.0. Version 1.4 is where they switched from 2.0 to 3.0 (without
+changing the Library directory to the one from 3.0 for some reason).
+
+The code in this package can be built with Borland C++ 2.0 and the compiled
+executables appear to be working perfectly fine. But when that version of the
+compiler was used to compile the "Return to the Shadowlands" source code (which
+is based on an earlier incarnation of this source code recreation), it caused
+problems. The code compiled without errors, but the compiled executable would
+always quit with the error message "Abnormal program termination".
+
+The reason for this error was that the compiler appeared to have forced the
+"grneeded" array (declared as "far" in ID_CA.C) into the main data segment
+instead of giving it its own far data segment. With this additional data in the
+main data segment, there was simply not enough space left for the stack and
+that is why the program aborted with an error message.
+
+It is unclear what caused this problem. The same source code compiles perfectly
+fine with Borland C++ 3.1 and produces an executable that actually works. If
+similar issues arise when working on mods based on this source code, try using
+Borland C++ 3.1 instead of whatever version you were using before.
+
+
+Special Thanks
+==============
+
+I would like to thank Jason Blochowiak, Adrian Carmack, John Carmack, Tom Hall,
+John Romero and Robert Prince for creating Commander Keen 4-6 in the first
+place.
+
+Special thanks to John Carmack (and the rest of id Software) for releasing the
+Wolfenstein 3-D and Spear of Destiny source code to the public in July 1995.
+
+Extra special thanks to the late Richard Mandel of Flat Rock Software and
+everybody else involved in the process of getting the source code of some of
+the games id Software made for Softdisk (Catacomb series, Hovertank, Keen
+Dreams) released to the public. I have learned a lot from the source code of
+these games and this project certainly would not have been possible without it.
+
+Thanks to PCKF user Multimania for supplying additional information regarding
+the names of functions and variables for Keen 4 and Keen 5.
+
+And last, but not least, I would like to thank NY00123 for figuring out how to
+get the compiler to recreate Keen 6 v1.5 and also for sharing a lot of valuable
+information about the "gamesrc-ver-recreation" project in various public posts
+on the RGB Classic Games Forum (among other places). That's where I first heard
+about the TDUMP utility, which is certainly a much better way to extract names
+from the debugging information that some executables came with. And using IDA
+to open executables and then make IDA generate ASM files that can be compared
+more easily using tools like FC in Windows/DOS is pretty much the best way to
+track down differences between those two executables without going insane.
+
+[END OF FILE]
\ No newline at end of file
diff --git a/16/keen456/ripnmake.bat b/16/keen456/ripnmake.bat
new file mode 100755
index 00000000..ab8b8dbc
--- /dev/null
+++ b/16/keen456/ripnmake.bat
@@ -0,0 +1,20 @@
+@echo off
+
+cd keen4-6\static
+
+echo Trying to extract data from KEEN 4 ...
+ck4patch ripck4.pat
+echo.
+
+echo Trying to extract data from KEEN 5 ...
+ck5patch ripck5.pat
+echo.
+
+echo Trying to extract data from KEEN 6 ...
+ck6patch ripck6.pat
+echo.
+
+echo Converting data files to .OBJ ...
+call make.bat
+
+cd ..\..
\ No newline at end of file