English Amiga Board


Go Back   English Amiga Board > Coders > Coders. General

 
 
Thread Tools
Old 18 February 2010, 14:11   #1
tnk2k
Registered User
 
Join Date: Apr 2009
Location: Uitgeest
Posts: 19
242 - virtual dreams - sourcecode

L.S.,

I've been trying to get my hands on the '242 / Virtual Dreams' sourcecode ( [ Show youtube player ])

Now i know the sourcecode has been sold to a few as i contacted the author (he doesn't have the code anymore). Does anybody have it and willing to share it with me?

Thanks!
tnk2k is offline  
Old 18 February 2010, 14:51   #2
StingRay
move.l #$c0ff33,throat
 
StingRay's Avatar
 
Join Date: Dec 2005
Location: Berlin/Joymoney
Posts: 6,863
Out of interest, why would you need the source? The demo is nothing more than an animation player (I suppose you are interested in the packing algo?). Anyway, you could always disassemble it you know.
StingRay is offline  
Old 23 February 2010, 13:54   #3
tnk2k
Registered User
 
Join Date: Apr 2009
Location: Uitgeest
Posts: 19
Is it just animation? Is there any good guide to dissamble?
tnk2k is offline  
Old 24 February 2010, 14:28   #4
victim
Registered User
 
Join Date: Mar 2009
Location: N/A
Posts: 23
Quote:
Originally Posted by tnk2k View Post
Is it just animation? Is there any good guide to dissamble?
Hi tnk2k !

I had found for some time ago this sample listing from John Eklund.
I think in the demo by Virtual Dreams will not do anything other than the routine below.

so long
Victim

Provides for easy presentation of material produced by the
aforementioned packer. Current Amiga version featuring non-realtime Huffman
depacking, realtime: (on 68020+) deltaframe 0-skipping,
blurring, x2 magnification and chunky-to-planar conversion, achieved through
extensive optimization and (Amiga-) Copper dependency. Typical frame rate between
10-20 frames per second. To improve the performance of the
labor-intensive blurring and chunky-to-planar conversions, every second line is
interleaved on the screen in an unusual way, using the copper to jump back and forth
between two separate memory areas containing even (original) and odd
(interpolated) screen lines. Fastmem recommended.

Here can you download the entire listing:
http://www.savage-crew.de/PlayChunky.zip

Code:
  
;John Eklund 1994

;Plays packed chunky animation with realtime chunky-to-planar and
;*2 magnification with interpolated pixels added between original pixels
;with simplified fast algorithm. Allocates, StoneDeCracks, makes 0-script,
;skips unchanged pixels (4*2 original 0's) when animating.

;For 68000 compatibility, change around line 248 !
;Silly really, but d7.w*2 IS faster on 020+ ! :-)

;Animation MUST be even 8 bytes - 64 pixels wide at 2*2
;Which is one full screen. due to fetch mode..

;The copper list on every second line sets the modulo to:
; Xplanar/8*Yplanar/2, that is half a screen plane down, and "back".
;Every second line (interpolated values) are written "below" all the
;original lines to facilitate "quick skips" ahead according to the
;delta 0-table. No line multiples and so on

;NO interleaved planes, normal!

;Plane 1:upper half=orig. lines
;    lower    =interpolated values
;Plane 2:etc..

;0-packer begins each frame in the table with one word that says
;in which delta state the frame starts (0/non-0)
;Str0Tab contains #words (4pixels) in the orig. chunky area. NOT line+column

;Min0s=4        ;Lowest # of consecutive 0-words for packing, 1=best!

nFrames=32
Xchunky=160        ;Original chunky size UNPACKED, #bytes=half!
Ychunky=97
Xplanar=Xchunky*2    ;Including approximated points
Yplanar=Ychunky*2
Xscreen=320
Yscreen=256
nPlanes=4
nCols=1<<nPlanes
Ystart=$2c
FrameSize=Xchunky*Ychunky/2    ;/2: Packed chunky, nibbles
AnimSize=FrameSize*nFrames

PlaneSize=Xscreen/8*Yscreen
ScrSize=PlaneSize*nPlanes

Str0Size=FrameSize*nFrames        ;To be on the safe side..

j:        movem.l    d1-d7/a0-a6,-(sp)
        move.l    4.w,a6

;    move.l    Packed+8(pc),d0        ;Original length in StoneCracked..
;    add.l    #VarSize,d0        ;Variables
        move.l    #TotalAny,d0
        moveq    #1,d1
        swap    d1            ;memf_any+clear
        jsr    -198(a6)
; move.l d0,tt
        move.l    d0,a5        ;a5=VarBase!
        beq.w    NoAnyMem
        add.l    #VarSize,d0    ;VarSize=even!!
        move.l    d0,Anim(a5)
        add.l    #AnimSize,d0
        move.l    d0,Str0Tab(a5)

        move.l    #TotalChip,d0
        move.l    #$10002,d1        ;Requirements=Chip
        jsr    -198(a6)        ;AllocMem
        move.l    d0,ChipStart(a5)
        beq.w    NoChipMem
        addq.l    #8,d0
        and.b    #$f8,d0        ;Even 8 bytes addr
        move.l    d0,CopChip(a5)
        add.l    #CopSize+8,d0
        and.b    #$f8,d0
        move.l    d0,Screen(a5)

        lea    CopCols+[nCols*4](pc),a1
        moveq    #nCols-1,d0
SetCols:    move.w    d0,d1
        lsl.b    #4,d1        ;=mulu #$111, faster or?!?..
        or.b    d0,d1
        lsl.w    #4,d1
        or.b    d0,d1
        move.w    d1,-(a1)
        subq.l    #2,a1
        dbf    d0,SetCols

        lea    BplPtr+2(pc),a1
        move.l    Screen(a5),d0
        moveq    #nPlanes-1,d1
BplLoop:    swap    d0
        move.w    d0,(a1)
        swap    d0
        move.w    d0,4(a1)
        addq.l    #8,a1
        add.l    #PlaneSize,d0
        dbf    d1,BplLoop

        lea    Cop(pc),a0
        move.l    CopChip(a5),a1
        lea    CopWait-Cop(a1),a2    ;=CinitSize(a1)..
        moveq    #CinitSize/2-1,d1
CopyCop:    move.w    (a0)+,(a1)+
        dbf    d1,CopyCop
; move.l #-2,(a1)
; bra.s nocop
;        move.l    a2,d0
;        move.w    d0,-(a2)    ;Set Cop2LcH+L (the loop method)
;        subq.l    #4,a2
;        swap    d0
;        move.w    d0,(a2)

    move.l    #Ystart*$1000000+$07fffe,d0        ;Wait
    move.l    #$01080000+[Xplanar/8*[Yplanar/2-1]-8],d1
                ;Down half the screen!
    move.l    #$010a0000+[Xplanar/8*[Yplanar/2-1]-8],d2
    move.l    #$01080000+[-[Xplanar/8*Yplanar/2+8]&$ffff],d3;Up again
    move.l    #$010a0000+[-[Xplanar/8*Yplanar/2+8]&$ffff],d4
    moveq    #Yplanar/2-1,d7
MakeCop:movem.l    d0/d1/d2,(a2)        ;Even wait + jump-down
    lea    4*3(a2),a2
    add.l    #$01000000,d0        ;Next line
    movem.l    d0/d3/d4,(a2)        ;Odd wait +jump-up on the next line
    lea    4*3(a2),a2
    add.l    #$01000000,d0
    dbf    d7,MakeCop
    move.l    d0,(a2)+
    move.l    #$01000200,(a2)+    ;0 bpls
    moveq    #-2,d0
    move.l    d0,(a2)
nocop:
        lea    GfxLib(pc),a1
        moveq    #0,d0
        jsr    -552(a6)    ;OpenLibrary
        move.l    d0,a0
        beq.w    LibError
        jsr    -132(a6)        ;Forbid
        move.l    $26(a0),oldcop1(a5)
        move.l    $32(a0),oldcop2(a5)
        lea    $dff000,a6
        move.w    #$4000,$9a(a6)        ;Shut down interrupts
        move.w    $02(a6),olddma(a5)
        bset    #7,olddma(a5)
wait:        tst.b    6(a6)
        bpl.s    wait
wait2:        cmp.b    #$2c+18,6(a6)
        bne.s    wait2
        move.w    #$7fff,$96(a6)

        move.w    #$8380,$96(a6)    ;bpl+cop
;        move.w    #$83c0,$96(a6)    ;bpl+cop+blt (BLTPRI=0)
        move.l    CopChip(a5),$80(a6)
    moveq    #0,d0
    move.w    d0,$88(a6)
    move.w    d0,$10e(a6)
;z:    cmp.w #$f8,$7c(a6)    ;Yuck--
;    bne.s noAGA
    move.w    d0,$1fc(a6)
;noAGA:
;    moveq    #-1,d0
;    bsr.w    WaitBlit
;    move.l    d0,$44(a6)    ;BLTAFWM+LWM

    lea    Packed(pc),a1    ;Packed source
    move.l    Anim(a5),a0    ;Depacked dest
    movem.l    a5/a6,-(sp)
    bsr.w    decrunch    ;De-StoneCrack
    movem.l    (sp)+,a5/a6

    bsr.w    Pack0        ;Make 0-script
    bsr.w    DeDelta        ;Make real frames
; bra.w    exit        ;TEST!

    move.l    Str0Tab(a5),a2    ;0-script, ONE time (pingpong=impossible!)
    move.w    #-1,CountAdd(a5)    ;NEG:ed immediately at frame 1 !

    bsr.s    Animate        ;Show frame 1 immediately!

Main:    btst    #2,$16(a6)    ;Right mouse button
    bne.s    noRB

    bsr.s    Animate

noRB:    btst    #6,$bfe001
    bne.s    Main
    bra.w    Exit

Animate:move.l    Anim(a5),a0
    move.w    Counter(a5),d0

; tst.w    CountAdd(a5)
; bpl.s    noStop
; cmp.w    #nFrames-2,d0
    cmp.w    #nFrames-1,d0    ;Last frame=corrupt! because of packer.
 beq.s    frDone            ;=rts, One-shit anim :)
;noStop:

    mulu    #FrameSize,d0
    add.l    d0,a0
;    and.w    #nFrames-1,Counter(a5)
    tst.w    Counter(a5)
    beq.s    nCount
    cmp.w    #nFrames-1,Counter(a5)
    bne.s    doAnim
nCount:    neg.w    CountAdd(a5)
doAnim:    move.w    CountAdd(a5),d1
    add.w    d1,Counter(a5)

    move.l    Screen(a5),a1

    moveq    #1,d7        ;Often used LSR value
    swap    d7
;    move.w    #Ychunky-1,d7

    move.w    #$0f0f,d4    ;Mask, low nibbles
;    move.w    #$f0f0,d5    ;Mask, high nibbles =UNNECESSARY !
    moveq    #4,d5        ;Often used shift value, optimized

;Str0Tab contains #words (4pixels) in the orig. chunky area
;unnec. moveq    #0,d6        ;d6=state, changed every interval
    tst.w    (a2)+        ;Frame starts in what state?
    bpl.s    notEnd        ;No change this picture! Oh..
frDone:    rts

notEnd:    seq    d6

NextStr:move.w    (a2)+,d7    ;#0/non-0-pixels ahead,above OR below
    bmi.s    frDone        ;"Negative terminated"
    not.b    d6        ;Flipped for every sequence
    bne.s    plotIt        ;d6= NOW not 0

;    move.b    d7,d1
;    lsr.w    #8,d0        ;d0=# 4 X-pixels(words) beyond whole line
;    bcc.s    noYchg        ;# unchanged lines = 0 (low byte)
;    ext.w    d1        ;Max #unchanged Y=127, AND #$ff otherwise
;    move.w    d1,d2
;    mulu    #Xchunky/2,d1        ;/2: 2 pixels/byte
;    mulu    #Xplanar/8*nPlanes*2,d2    ;*2:Every 2nd screen line=interpolated
;    add.w    d0,d1        ;Chunky skip
;    add.w    d0,d2        ;Planar skip
;    bra.s    lined
;noYchg:
    lea    (a1,d7.w),a1    ;Skip ahead in planar area, the screen
    lea    (a0,d7.w*2),a0    ;Skip ahead in chunky area (68020+)

; Replace the above line (d7.w*2) with these two below for 68000 !
;    add.w    d7,d7        ;Faster than lsl #1
;    lea    (a0,d7.w),a0    ;Skip ahead in chunky area

    bra.s    NextStr
;lined:

plotIt:    subq.w    #1,d7        ;dbf

Plot8:
;    move.w    #Xchunky/4-1,d6    ;/4:Make 4 orig.Xpixels at a time,2 per byte
    swap    d7        ;d7.w = #1, for quick LSR

;approx:
    move.w    (a0)+,d0    ;Upper line, 4 orig.pixels (nibbles)
    move.w    d0,d1
    lsr.w    d5,d0        ;d5=#4, For lower nibbles
    and.b    d4,d0    ;Lower nibbles, Note! "the left pixels" 1 + 3

    move.w    d0,d2        ;For future use below.. Line in-between!

    and.w    d4,d1        ;Lower nibbles, "the right pixels" 2 + 4
    add.w    d1,d0
    lsr.w    d7,d0    ;d0.w lower = upper middle pixels 1 + 3 DONE d7=#1
    and.b    d4,d0        ;Get rid of junk

    move.w    d1,d3
    lsr.w    #8,d3        ;Orig. pixel 2 shifted down, for middle pix.2
    add.b    d2,d3        ;d2 = orig.pixel 3 shifted down
    lsl.w    #8-1,d3        ;lsr #1 optimized away, "clr.b" below!

; swap    d0
; move.w    (a0)+,d0
; ror.w    #8,d0
; move.b    d0,d3    ;Alternative to (a0) below + the one highest above
;save this instead (doubt that it will be faster)

    move.b    (a0),d3        ;Get rid of bit 0 from previous!
    lsr.b    d5,d3        ;d3=orig.pixel 5, d5=#4
    add.b    d1,d3
    lsr.b    d7,d3    ;d3 low = middle pixel 2 + middle pixel 4 DONE d7=#1

;Sequence, upper line, 1 nibble at a time, simplified in CtoP!
;d2    0x00    orig. pixel 1
;d0    0x00    average pixel 1
;d1    0x00    orig. pixel 2
;d3    0x00    average pixel 2
;d2    000x    orig. pixel 3
;d0    000x    average pixel 3
;d1    000x    orig. pixel 4
;d3    000x    average pixel 4

;    swap    d1    ;Unfortunately done in CtoP,
            ;..unnecessary for lower line, below
    bsr.s    CtoP
;    swap    d1

    lsr.w    d5,d2    ;Compensation, d2 used earlier! d5=#4

    move.w    Xchunky/2-2(a0),d0    ;/2: nibbles
    move.w    d0,d3

    lsr.w    d5,d0    ;For lower nibbles d5=#4
    and.b    d4,d0    ;Lower nibbles, Note! "the left pixels" 1 + 3
    and.w    d4,d3    ;Lower nibbles, "the right pixels" 2 + 4
;Upper:
;d2=Lower nibbles, "the left pixels" 1 + 3
;d1=Lower nibbles, "the right pixels" 2 + 4

    add.w    d0,d2
    move.w    d2,d0    ;d0=vertical average 1 + 3 unshifted,for center average

    add.w    d3,d1
    move.w    d1,d3    ;d3=vertical average 2 + 4 unshifted, for center average

    add.w    d3,d0
    lsr.w    #2,d0    ;d0 = Central average pixel 1 + 3 DONE
    and.b    d4,d0

    lsr.w    #8,d3    ;Shift down vertical average 2
    add.b    d2,d3    ;d2.b=vertical average 3, d3 = Central average pixel 2

    lsr.w    d7,d2    ;d2.w low = Vertical average pixels 1 + 3 DONE d7=#1
    and.b    d4,d2        ;Get rid of junk

    lsl.w    #8-2,d3    ;LSR #2 + AND optimized away, low byte 0:ed below!
    move.b    (a0),d7
    lsr.b    d5,d7    ;d7 = next upper orig. pixel 5 (becoming 1) d5=#4
    move.b    Xchunky/2(a0),d3    ;/2: nibbles
    lsr.b    d5,d3    ;d3=next lower orig. pixel 5 d5=#4
    add.b    d7,d3
    add.b    d1,d3    ;d1.b = vertical average pixel 4
    lsr.b    #2,d3    ;d3 = Central average pixel 2 + 4 DONE

    lsr.w    #1,d1    ;d1.w = vertical average pixels 2 + 4 DONE d7=#1
    and.b    d4,d1

;Sequence, lower line
;d2    0x00    Vertical average 1
;d0    0x00    Central average 1
;d1    0x00    Vertical average 2
;d3    0x00    Central average 2
;d2    000x    Vertical average 3
;d0    000x    Cebtral average 3
;d1    000x    Vertical average 4
;d3    000x    Central average 4

    lea    Xscreen/8*Yplanar/2-1(a1),a1;Line below, between orig.lines
    bsr.s    CtoP    ;in reality this is Yplanar/2 below upper "block"!
    lea    -Xscreen/8*Yplanar/2(a1),a1    ;The original line

;    dbf    d6,approx

;    lea    Xscreen/8*nPlanes*2-[Xplanar/8](a1),a1    ;Plane 0 next line
;/\ Unnecessary having copper list with modulo every second line!

    swap    d7        ;Register shortage..
    dbf    d7,Plot8
    bra.w    NextStr        ;Next interval (0/non0) from the table
;    rts

CtoP:

;Sequence, 1 nibble at a time
;d2    0x00    orig. pixel 1
;d0    0x00    average pixel 1
;d1    0x00    orig. pixel 2
;d3    0x00    average pixel 2
;d2    000x    orig. pixel 3
;d0    000x    average pixel 3
;d1    000x    orig. pixel 4
;d3    000x    average pixel 4

    lsl.w    d5,d0    ;d5=#4
    or.w    d1,d0    ;d0=complete 4 pixels!
    lsl.w    d5,d2
    or.w    d2,d3    ;d3=complete 4 pixels!

;After having added above.. d1 + d2 saved.
;d3    x000    orig. pixel 1
;d0    x000    average pixel 1
;d0    0x00    orig. pixel 2
;d3    0x00    average pixel 2
;d3    00x0    orig. pixel 3
;d0    00x0    average pixel 3
;d0    000x    orig. pixel 4
;d3    000x    average pixel 4

    swap    d1
    swap    d6
    move.w    #2-1,d1

CPloop:
; REPT 2
    add.w    d3,d3
    roxl.b    #1,d4    ;Becomes 8 pixels in 4 planes
    add.w    d3,d3
    roxl.b    #1,d5
    add.w    d3,d3
    roxl.b    #1,d6
    add.w    d3,d3
    roxl.b    #1,d7

    add.w    d0,d0
    roxl.b    #1,d4
    add.w    d0,d0
    roxl.b    #1,d5
    add.w    d0,d0
    roxl.b    #1,d6
    add.w    d0,d0
    roxl.b    #1,d7

    add.w    d0,d0
    roxl.b    #1,d4
    add.w    d0,d0
    roxl.b    #1,d5
    add.w    d0,d0
    roxl.b    #1,d6
    add.w    d0,d0
    roxl.b    #1,d7

    add.w    d3,d3
    roxl.b    #1,d4
    add.w    d3,d3
    roxl.b    #1,d5
    add.w    d3,d3
    roxl.b    #1,d6
    add.w    d3,d3
    roxl.b    #1,d7
; ENDR
    dbf    d1,CPloop    ;Fits in cache!

;    add.w    d3,d3
;    roxl.b    #1,d4
;    add.w    d3,d3
;    roxl.b    #1,d5
;    add.w    d3,d3
;    roxl.b    #1,d6
;    add.w    d3,d3
;    roxl.b    #1,d7

;    add.w    d0,d0
;    roxl.b    #1,d4
;    add.w    d0,d0
;    roxl.b    #1,d5
;    add.w    d0,d0
;    roxl.b    #1,d6
;    add.w    d0,d0
;    roxl.b    #1,d7

;    add.w    d0,d0
;    roxl.b    #1,d4
;    add.w    d0,d0
;    roxl.b    #1,d5
;    add.w    d0,d0
;    roxl.b    #1,d6
;    add.w    d0,d0
;    roxl.b    #1,d7

;    add.w    d3,d3
;    roxl.b    #1,d4
;;    move.b    d4,Xscreen/8*3(a1)
;    add.w    d3,d3
;    roxl.b    #1,d5
;;    move.b    d5,Xscreen/8*2(a1)
;    add.w    d3,d3
;    roxl.b    #1,d6
;;    move.b    d6,Xscreen/8(a1)    ;Planes stored interleaved
;    add.w    d3,d3
;    roxl.b    #1,d7
;    ENDR

    move.b d6,PlaneSize(a1)        ;Planes stored normally
        swap    d6        ;Restore trashed registers
    move.b d5,PlaneSize*2(a1)
        moveq    #4,d5
        swap    d1
    move.b d4,PlaneSize*3(a1)
        move.w    #$0f0f,d4    ;Mask, low nibbles
    move.b d7,(a1)+
        move.w    #1,d7        ;LSR value. Note! .W, NOT moveq!!
    rts

;Script-author, writes a script with number of 0's / non-0's
Pack0:    move.l    Anim(a5),a0    ;Depacked, delta-nibbles
    lea    FrameSize(a0),a0
    move.l    Str0Tab(a5),a2
    moveq    #0,d3        ;Important! Negative word->finished plotting!
    moveq    #nFrames-1,d7

    move.w    #$ff,(a2)+
    move.w    #FrameSize/2,(a2)+    ;Initialization, Frame1="full"
    move.w    #-1,(a2)+        ;End of frame 1

tstFr0:    moveq    #0,d0
    moveq    #0,d1
    move.w    #FrameSize/2-1,d6    ;/2: test words
;    move.w    #[FrameSize-[Xchunky/2]]/2-1,d6
    move.b    2(a0),d1        ;Include pixel 5 (next word)
    or.b    Xchunky/2+2(a0),d1    ;"inter-word intermediate" :)
    lsr.b    #4,d1            ;Upper nibble=pixel5
    or.w    (a0),d1
    or.w    Xchunky/2(a0),d1    ;Initialize start state, /2: nibbles
    sne    d3
    move.w    d3,(a2)+        ;Word 1 each frame = starting state
tst0:    move.w    (a0)+,d1
    move.b    (a0),d2
    or.b    Xchunky/2(a0),d2
    lsr.b    #4,d2
    or.b    d2,d1
    or.w    Xchunky/2-2(a0),d1
    bne.s    not0
    bclr    #0,d3
    beq.s    noChg0
    bra.s    chgTo0
not0:    bset    #0,d3
    bne.s    noChg0

Last edited by victim; 25 February 2010 at 01:21.
victim is offline  
Old 05 March 2010, 16:24   #5
tnk2k
Registered User
 
Join Date: Apr 2009
Location: Uitgeest
Posts: 19
Very nice! Thanks!
tnk2k is offline  
 


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

Similar Threads
Thread Thread Starter Forum Replies Last Post
Wanted: Wasted Dreams (Amiga CD, Digital Dreams Entertainment) dex MarketPlace 1 11 August 2012 15:52
Fairlight & Virtual Dreams 242 Amiga-demomusic Remix trackah123 Nostalgia & memories 6 10 September 2008 23:38
Virtual Dreams Demos MortimerTwang request.Demos 1 13 April 2005 01:42
Questions about Virtual Dreams Amiga1992 request.Demos 14 04 September 2002 19:33
Virtual Dreams 242 Stormlord request.Modules 2 03 October 2001 11:07

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

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

Forum Jump


All times are GMT +2. The time now is 04:28.

Top

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