Faster fade out code?

Started by DildoKKKobold, 09/20/2015, 11:30 AM

Previous topic - Next topic

0 Members and 1 Guest are viewing this topic.

touko

#50
i made some fade out/in in this intro some times ago :
https://youtu.be/B3pdwEza6j4

elmer

Quote from: touko on 12/02/2016, 03:26 AMi made some fade out/in in this intro some times ago :
https://youtu.be/B3pdwEza6j4
That looks nice!  :)

So what technique did you use for the processing each step of the fade up/down?


Quote from: ccovell on 12/02/2016, 01:14 AMI have no stake in this, but thinking down the road it might be better to add more granularity (0..15 or more) right now.  For example, many Sega games have more levels of fading by fading out Red & Green at different speeds before finally doing Blue... and it looks fantastic and far smoother than 8 steps as on the PCE.

I did something similar (using lookup tables) for my HuZero game.
I haven't heard of that stepping technique before, it sounds interesting.

Do you have any more details?

It's trivial to switch to a 0..15 range, even if I'm only processing 8 steps, so I've done that.

I definitely agree with using a table-based approach ... it gives you the flexibility to change the tables and get a fade-to-white, or a fade-to-sepia, or to correct for any gamma differences.

For HuC, I suspect that it's just a case of the tradeoff between quality and memory usage for the tables.

I'm also limited by trying to keep compatibility with HuCard usage rather then just using self-modifying code.

Here's an implementation that uses a single 64-byte table for a simple 8-step fade ... can anyone suggest improvements?

; fade_colors(int *psrc [__si], int *pdst [__di], char count, char level)
; ----
; fade down an array of colors
; ----
; psrc:  source buffer
; pdst:  destination buffer
; count: # of colors, (0-128)
; level: level of fading (0 = black, 7 = full)
; ----
; color: color value,   GREEN:  bit 6-8
;                       RED:    bit 3-5
;                       BLUE:   bit 0-2
; ----

_fade_colors.4: asl     a                       ; 2 fade level (0-15)
                asl     a                       ; 2
                and     #$38                    ; 2
                sta     <__ah                   ; 4

                lda     <__al                   ; 4 # of colors
                beq     .l2                     ; 2
                asl     a                       ; 2

                phx                             ; 3

                ; 129 cycle inner loop.
                ; fade GREEN

.l1:            dey                             ; 2
                lda     [__si],y                ; 7 src color hi-byte
                dey                             ; 2
                lsr     a                       ; 2
                lda     [__si],y                ; 7 src color lo-byte
                iny                             ; 2
                sta     <__al                   ; 4
                rol     a                       ; 2
                rol     a                       ; 2
                rol     a                       ; 2
                and     #7                      ; 2
                ora     <__ah                   ; 4
                tax                             ; 2
                lda     fade_table,x            ; 5
                asl     a                       ; 2
                asl     a                       ; 2
                asl     a                       ; 2
                tax                             ; 2

                ; fade RED

                lda     <__al                   ; 4 src color lo-byte
                ror     a                       ; 2
                ror     a                       ; 2
                ror     a                       ; 2
                and     #7                      ; 2
                ora     <__ah                   ; 4
                sax                             ; 3
                ora     fade_table,x            ; 5
                asl     a                       ; 2
                asl     a                       ; 2
                asl     a                       ; 2
                tax                             ; 2

                cla                             ; 2
                rol     a                       ; 2
                sta     [__di],y                ; 7 dst color hi-byte
                dey                             ; 2

                ; fade BLUE

                lda     <__al                   ; 4 src color lo-byte
                and     #7                      ; 2
                ora     <__ah                   ; 4
                sax                             ; 3
                ora     fade_table,x            ; 5
                sta     [__di],y                ; 7 dst color lo-byte
                cpy     #0                      ; 2
                bne     .l1                     ; 4

                plx                             ; 4
.l2:            rts                             ; 7

fade_table:     .db     0, 0, 0, 0, 0, 0, 0, 0
                .db     0, 0, 0, 0, 1, 1, 1, 1
                .db     0, 0, 1, 1, 1, 1, 2, 2
                .db     0, 0, 1, 1, 2, 2, 3, 3
                .db     0, 1, 1, 2, 2, 3, 3, 4
                .db     0, 1, 1, 2, 3, 4, 4, 5
                .db     0, 1, 2, 3, 3, 4, 5, 6
                .db     0, 1, 2, 3, 4, 5, 6, 7

touko

QuoteSo what technique did you use for the processing each step of the fade up/down?
The simpliest, add/sub 1 for each RGB componant .

elmer

#53
Quote from: touko on 12/02/2016, 12:23 PM
QuoteSo what technique did you use for the processing each step of the fade up/down?
The simpliest, add/sub 1 for each RGB componant .
Well, the fade-down is easy ... but what did you do for the fade-up?  :-k

Are you using the simple "add 1 if not at target" for each component?

That tends to grey things out a little during the fade-up, like this ...

Target GRB : 456

Step 0 GRB : 000
Step 1 GRB : 111
Step 2 GRB : 222
Step 3 GRB : 333
Step 4 GRB : 444
Step 5 GRB : 455
Step 6 GRB : 456


It's not a bad effect, and most people don't notice/care about it.

Just curious.


Quote from: elmer on 12/02/2016, 11:35 AM
Quote from: ccovell on 12/02/2016, 01:14 AMI have no stake in this, but thinking down the road it might be better to add more granularity (0..15 or more) right now.  For example, many Sega games have more levels of fading by fading out Red & Green at different speeds before finally doing Blue... and it looks fantastic and far smoother than 8 steps as on the PCE.

I did something similar (using lookup tables) for my HuZero game.
I haven't heard of that stepping technique before, it sounds interesting.

Do you have any more details?
I presume that you're talking about taking advantage ot the human eye's perception of brightness.

The RGB to Y (brightness) formula is ...

Y = 0.299R + 0.587G + 0.114B

So, to reduce percieved brightness, you need to remove more of the green than you do of the blue.

From a practical implementation POV, do you mean something like this?  :-k

It changes things to a (0..17) range instead of (0..15).

This would provide a sort-of-half-step in the color transition, and delay the blue and red component fades.

fade_table_g:   .db     0, 0, 0, 0, 0, 0, 0, 0
                .db     0, 0, 0, 0, 0, 0, 0, 0
fade_table_r:   .db     0, 0, 0, 0, 0, 0, 0, 0
fade_table_b:   .db     0, 0, 0, 0, 0, 0, 0, 0
                .db     0, 0, 0, 0, 1, 1, 1, 1
                .db     0, 0, 0, 1, 1, 1, 1, 1
                .db     0, 0, 1, 1, 1, 1, 2, 2
                .db     0, 0, 1, 1, 1, 2, 2, 2
                .db     0, 0, 1, 1, 2, 2, 2, 3
                .db     0, 0, 1, 1, 2, 2, 3, 3
                .db     0, 1, 1, 2, 2, 3, 3, 4
                .db     0, 1, 1, 2, 2, 3, 3, 4
                .db     0, 1, 1, 2, 3, 3, 4, 4
                .db     0, 1, 1, 2, 3, 3, 4, 5
                .db     0, 1, 2, 2, 3, 4, 5, 5
                .db     0, 1, 2, 2, 3, 4, 5, 6
                .db     0, 1, 2, 3, 4, 4, 5, 6
                .db     0, 1, 2, 3, 4, 5, 6, 7
                .db     0, 1, 2, 3, 4, 5, 6, 7
                .db     0, 1, 2, 3, 4, 5, 6, 7
                .db     0, 1, 2, 3, 4, 5, 6, 7


Or just this easier-to-read version with step (0..9) ...


fade_table_g:   .db     0, 0, 0, 0, 0, 0, 0, 0
fade_table_r:   .db     0, 0, 0, 0, 0, 0, 0, 0
fade_table_b:   .db     0, 0, 0, 0, 0, 0, 0, 0
                .db     0, 0, 0, 0, 1, 1, 1, 1
                .db     0, 0, 1, 1, 1, 1, 2, 2
                .db     0, 0, 1, 1, 2, 2, 3, 3
                .db     0, 1, 1, 2, 2, 3, 3, 4
                .db     0, 1, 1, 2, 3, 4, 4, 5
                .db     0, 1, 2, 3, 3, 4, 5, 6
                .db     0, 1, 2, 3, 4, 5, 6, 7
                .db     0, 1, 2, 3, 4, 5, 6, 7
                .db     0, 1, 2, 3, 4, 5, 6, 7


touko

#54
Quotebut what did you do for the fade-up?
You start with an entire black palette, and you add 1 for each component until you reach the good palette .
in fact for fade in and fade out i have a palette for reference to reach (black for a fade out, and the object's palette for fade in) ,i read directly the corresponding colors in the VCE,i make the fade and store it in a buffer(for sending later with TIA) .
I have a 256 bytes buffer for fading multiple palettes at same time .

QuoteIt's not a bad effect, and most people don't notice/care about it.
You're right, but is not noticeable as long as your fade is fast enough.
I think for best result, you must nomalise all your RGB component for each color first to avoid a dominant color at the end of fade .
EG : reaching a 444 or 222,333 and start the add/sub after that,and you end with 0 for each component . .

TurboXray

I personally like the idea of the fade table, for speed reasons. As in, fade is actually just a "brightness" (loosely termed) state of the palette, and fade is the transition from one level of brightness to another over time.

 But of course, I'd say make this not a built in library function - but something the programmer can just include. I mean, there's no critical reason why it should be the very main bank of the main lib - so having it as a function with ASM inside of it, is no slower than the far call to the far end of the main lib. Speaking of which, there's probably a good number of stuff that probably should be in the main lib bank to begin with. And some stuff could easily be moved to include-able functions. I'm going to look into this as soon as winter break starts.

ccovell

My table was a wasteful 512 bytes, mapping all 512 colours to the next step down... so it's a fadeout routine only.  Anyway, the code (minus the table):
Fade_Down: ;Fades a specified palette down 1 step!
;A = Palette entry (0,$10,$20,$30...)
;X = 0/1 = BG or Sprite
;-------------------------------------------------------
;copy our specified palette from VCE to RAM
sta $0402       ;Point to colours
stx $0403
pha
phx
phy
TAI $0404,temp_pal,32
;----------
clx
.fade_loop:
lda temp_pal,X
tay
lda temp_pal+1,X ;(MSB is 0 or 1)
and #1 ;All other bits were set in VCE.
beq .lopal
;MSB was high; (leave it as-is...)
lda PALFADE1HiTblLSB,Y ;Get LSB
sta temp_pal,X
cpy #64 ;64th entry and up, MSB=1
bcs .next_entry
.zeromsb:
stz temp_pal+1,X
bra .next_entry
;----------
.lopal: ;MSB will always be zero anyway
lda PALFADE1LoTblLSB,Y ;Get LSB
sta temp_pal,X
.next_entry:
inx
inx
cpx #32
bne .fade_loop
;--------
;now copy RAM back to VCE
ply
plx
pla
sta $0402       ;Point to colours
stx $0403
TIA temp_pal,$0404,32
; A, Y, and X should be preserved here.
rts

TurboXray

So.. maybe this would be helpful?

The call code...
      ldy iterations 
      ldx #low(xfer_source)
      clc
      jsr xfer_ZP

The self modifying code sitting in... Zeropage!
xfer_entry:
.loop
      tia source,dest,num
      set                               ;2
      adc #$nn                          ;5 (RMW+T)
    bcc .skip                           ;4:2
      inc <low((.loop & 0xff)+2)+1      ;6
      clc                               ;2
.skip
      dey                               ;2
      bne .loop                         ;4
    rts                                 ;7

xfer_source = (.loop & 0xff) + BASE_ZP + 1
xfer_dest = (.loop & 0xff) + BASE_ZP + 3
xfer_num = (.loop & 0xff) + BASE_ZP + 5     
xfer_ZP = (.loop & 0xff) + BASE_ZP 
Of course, it needs to be copied at least once to ZP buffer. That's what all the address translations are for via the equates.

elmer

Quote from: TurboXray on 12/02/2016, 05:37 PMOf course, it needs to be copied at least once to ZP buffer. That's what all the address translations are for via the equates.
Yes, I do like using a self-modifying Txx instruction in ZP.  :wink:

This is what I've got, which uses HuC's __fastcall convention to have the compiler-itself set up the ZP locations that it can ...

; --------
; Alternate names when the parameter-passing area is used for
; a self-modifying Txx instruction.
;

__tc    = $20F8
__ts    = $20F9
__td    = $20FB
__tl    = $20FD
__tr    = $20FF

; set_colors(int *pbuffer [__ts] )
; set_colors(int index [color_reg], int *pbuffer [__ts], int count [__tl] )
; ----
; index:   index in the palette (0-511)
; pbuffer: source buffer
; count:   # of colors, (1-512)
; ----

_set_colors.1:  stz     color_reg_l
                stz     color_reg_h

                stz     <__tl+0
                lda     #>512
                sta     <__tl+1

_set_colors.3:  lda     #$E3 ; TIA
                sta     <__tc
                lda     #$60 ; RTS
                sta     <__tr
                lda     #<color_data
                sta     <__td+0
                lda     #>color_data
                sta     <__td+1
                asl     <__tl+0
                rol     <__tl+1
                jmp     __tc

TurboXray

Yeah, classic Txx in ram setup.
 
But what I posted was a "safe" version. So that you don't delayed interrupts (in this case, since it's in vblank, the TIRQ routine), through smaller transfers and a small/fast iteration overhead.

 It can also work for active video, with scanline interrupts and TIMER interrupts all firing like mad. The sample playback might be a little bit of jitter, but nothing Genesis cringe worthy. And the VDC buffer for next line should be able to absorb any delay (as long as the routine is tight). The best of all words: TIMER, H-int, and Txx availability. And the cost, if you did 32byte transfers, is 8cycles per byte instead of the 7cycles per byte. It makes Txx more usable IMO. Plus, it's a chance to use the T flag... who doesn't like using the T flag???

elmer

#60
Quote from: TurboXray on 12/03/2016, 04:46 PMBut what I posted was a "safe" version. So that you don't delayed interrupts (in this case, since it's in vblank, the TIRQ routine), through smaller transfers and a small/fast iteration overhead.
Good point!  :wink:

I was trying to keep a similar interface to the original functions which read a single sample, and I was thinking that they'd be run after a vsync() in order to avoid snow on the screen.

But you're right, I should still limit the TAI size in order to avoid blocking the TIMER interrupt.

My bad.  :oops:


QuotePlus, it's a chance to use the T flag... who doesn't like using the T flag???
Hahaha ... also a good point, but keeping the low-byte of the address in the A reg and doing ...

      adc #$20                          ;2
      sta <low((.loop & 0xff)+2)        ;4

... is a cycle faster, and it avoids messing with my stack-pointer-in-X.

Of course ... I throw away that cycle with the setup and the JSR, but that's a tradeoff for not needing a permanent routine in ZP.

There's certainly an argument for have a few of these Txx-32-byte subroutines in regular RAM to use for self-modifying code, and IIRC, HuC already has one somewhere.  :-k

Here's a corrected code, and of course, things are much cleaner in the CDROM version ...

; --------
; Alternate names when the parameter-passing area is used for
; a self-modifying Txx instruction.
;

__tc    = $20F8
__ts    = $20F9
__td    = $20FB
__tl    = $20FD
__tr    = $20FF

; set_colors(int *pbuffer [__ts] )
; set_colors(int index [color_reg], int *pbuffer [__ts], unsigned char count [acc] )
; ----
; index:   index in the palette (0-511)
; pbuffer: source buffer
; count:   # of 16-color palettes, (1-32)
; ----

_set_colors.1:  stz     color_reg_l
                stz     color_reg_h
                lda     #32

_set_colors.3:  tay
.if (!CDROM)
                lda     #$E3 ; TIA
                sta     <__tc
                lda     #$60 ; RTS
                sta     <__tr
                lda     #$04
                sta     <__td+0
                sta     <__td+1
lda     #$20
                sta     <__tl+0
                stz     <__tl+1
                lda     <__ts+0
.l1:            jsr     __tc
                adc     #$20
                sta     <__ts+0
                bcc     .l2
                inc     <__ts+1
.l2:            dey
                bne     .l1
                rts
.else
                lda     <__ts+1
                sta     .l1+2
                lda     <__ts+0
                sta     .l1+1
.l1:            tia     $0000,color_data,$0020
                adc     #$20
                sta     .l1+1
                bcc     .l2
                inc     .l1+2
.l2:            dey
                bne     .l1
                rts
.endif

TurboXray

Quote from: elmer on 12/03/2016, 07:41 PM
QuotePlus, it's a chance to use the T flag... who doesn't like using the T flag???
Hahaha ... also a good point, but keeping the low-byte of the address in the A reg and doing ...

      adc #$20                          ;2
      sta <low((.loop & 0xff)+2)        ;4

... is a cycle faster, and it avoids messing with my stack-pointer-in-X.

Of course ... I throw away that cycle with the setup and the JSR, but that's a tradeoff for not needing a permanent routine in ZP.
Good catch! My code is actually a little bit longer (I clipped it for the post), as it was meant for a demoscene part where it transfers two 28bytes segments, then sends a sample to the DAC - on large 90k cpu cycle loop. It's one of those dual circular interference patterns things, but translucent like the good ones.

ccovell

Psychic World on the Sega Master System had a pretty smooth and nice-looking fade in & out routine, so I wanted to find out how it did it.  Turns out it was a very simple 3-step process: for fade-outs, ramp down the red channel to zero, then do the same with green and blue sequentially.  Almost a bit too primitive, but it actually looks good in-game.

The SMS has only 3 shades of each colour channel (compared to the 7 per on the PCE) so a fade would have only a total of 4 steps if all 3 channels were simply faded out at the same time.  Doing it sequentially gives 10 steps total.  I'm sure similarly nice effects can be achieved on the PCE.

IMG
Above, using the SMS' limited colour space.

Arkhan Asylum

Quote from: ccovell on 12/11/2016, 09:06 PMPsychic World on the Sega Master System had a pretty smooth and nice-looking fade in & out routine, so I wanted to find out how it did it.  Turns out it was a very simple 3-step process: for fade-outs, ramp down the red channel to zero, then do the same with green and blue sequentially.  Almost a bit too primitive, but it actually looks good in-game.
I was doing this for Inferno on MSX, but the excessive amount of red in the game made it look pretty stupid, lol.

I ended up just going with a normal fade instead. 
This "max-level forum psycho" (:lol:) destroyed TWO PC Engine groups in rage: one by Aaron Lambert on Facebook "Because Chris 'Shadowland' Runyon!," then the other by Aaron Nanto "Because Le NightWolve!" Him and PCE Aarons don't have a good track record together... Both times he blamed the Aarons in a "Look-what-you-made-us-do?!" manner, never himself nor his deranged, destructive, toxic turbo troll gang!

TurboXray

Chris, do you have a gif of Sonic's fade out (on the Genesis)?

ccovell


elmer

Quote from: ccovell on 12/11/2016, 09:06 PMPsychic World on the Sega Master System had a pretty smooth and nice-looking fade in & out routine, so I wanted to find out how it did it.  Turns out it was a very simple 3-step process: for fade-outs, ramp down the red channel to zero, then do the same with green and blue sequentially.  Almost a bit too primitive, but it actually looks good in-game.
That's an interesting effect ... thanks for sharing that!  :D

I don't know (yet) if I like if I like it, or not, but it's definitely "effective".

Arkhan Asylum

Quote from: elmer on 12/12/2016, 01:33 AM
Quote from: ccovell on 12/11/2016, 09:06 PMPsychic World on the Sega Master System had a pretty smooth and nice-looking fade in & out routine, so I wanted to find out how it did it.  Turns out it was a very simple 3-step process: for fade-outs, ramp down the red channel to zero, then do the same with green and blue sequentially.  Almost a bit too primitive, but it actually looks good in-game.
That's an interesting effect ... thanks for sharing that!  :D

I don't know (yet) if I like if I like it, or not, but it's definitely "effective".
there's alot of interesting fades you can do if you focus on blue-shenanigans, but most people refer to them as coding errors/bugs/not knowing what you're doing.

As opposed to just wanting a weird blue swirly fade that looks cool.

This "max-level forum psycho" (:lol:) destroyed TWO PC Engine groups in rage: one by Aaron Lambert on Facebook "Because Chris 'Shadowland' Runyon!," then the other by Aaron Nanto "Because Le NightWolve!" Him and PCE Aarons don't have a good track record together... Both times he blamed the Aarons in a "Look-what-you-made-us-do?!" manner, never himself nor his deranged, destructive, toxic turbo troll gang!

ccovell

Quote from: Psycho Arkhan on 12/12/2016, 02:23 AMthere's alot of interesting fades you can do if you focus on blue-shenanigans, but most people refer to them as coding errors/bugs/not knowing what you're doing.
I beg to differ.  I'd call it Sega's signature style on the Genesis.

TurboXray

I don't think Arkhan is saying its wrong, just that people perceive it as wrong - for whatever reason they apply (bug/unknowledgeable/etc).

 Check this out:
http://info.sonicretro.org/SCHG_How-to:Improve_the_fade_in%5Cfade_out_progression_routines_in_Sonic_1
QuoteFrom Sonic Team's point of view, it may not be incorrect and is possibly intentional, however, from a logical point of view, this is incorrect fading
Some people's kids.. I swear.

Arkhan Asylum

Yeah, I mean, what the fuck is "incorrect" fading, anyways.   Did it make it to the target colors eventually?  Did it look neat?

I find it pretty derpy that people commenting on stuff from the 80s are saying fades that involve color swirlies, or something are wrong.

I mean if it fades and never makes it to where you want, or it causes actual software issues, I'd say that is wrong.

but, fades are inherently lawless.   You can fade whatever to whatever. 

People seem to think the only correct fade is one that fades from black or to black completely in unison.

This "max-level forum psycho" (:lol:) destroyed TWO PC Engine groups in rage: one by Aaron Lambert on Facebook "Because Chris 'Shadowland' Runyon!," then the other by Aaron Nanto "Because Le NightWolve!" Him and PCE Aarons don't have a good track record together... Both times he blamed the Aarons in a "Look-what-you-made-us-do?!" manner, never himself nor his deranged, destructive, toxic turbo troll gang!

Gredler

So you'd say it's a derpy lerpy?

Thank you, I'll be here all week.

Arkhan Asylum

Quote from: Gredler on 12/12/2016, 04:47 PMSo you'd say it's a derpy lerpy?

Thank you, I'll be here all week.
yes.  exactly, lol.

I did a normalized palette fade (read: correct by codesnobbery standards), and it looked worse than the "wrong fade" that goes to grays first. 

Sometimes "right" can get bent. 
This "max-level forum psycho" (:lol:) destroyed TWO PC Engine groups in rage: one by Aaron Lambert on Facebook "Because Chris 'Shadowland' Runyon!," then the other by Aaron Nanto "Because Le NightWolve!" Him and PCE Aarons don't have a good track record together... Both times he blamed the Aarons in a "Look-what-you-made-us-do?!" manner, never himself nor his deranged, destructive, toxic turbo troll gang!

ccovell

#73
Heck, my favourite fade is the Game Over one from NES Ninja Gaiden.  ;-D

edit:
Quote from: TurboXray on 12/12/2016, 12:06 PMCheck this out:
http://info.sonicretro.org/SCHG_How-to:Improve_the_fade_in%5Cfade_out_progression_routines_in_Sonic_1
Holy sperglord-levels of missing-the-point on that page!  The eye is sensitive to the different channels of colour differently, and so Sega was exploiting that, not to mention fading through 8 levels only will look too abrupt and might look like it's "shaking" to some viewers.  :-P

Arkhan Asylum

Quote from: ccovell on 12/12/2016, 05:59 PMHoly sperglord-levels of missing-the-point on that page!
I loled while eating a cupcake.

Did you know cupcake can come out of your nose?

I do now.

Blue fades are probably one of the most interesting things to dick with, as blue is the most interesting of the 3 colors in terms of our eyes perceiving it.

This "max-level forum psycho" (:lol:) destroyed TWO PC Engine groups in rage: one by Aaron Lambert on Facebook "Because Chris 'Shadowland' Runyon!," then the other by Aaron Nanto "Because Le NightWolve!" Him and PCE Aarons don't have a good track record together... Both times he blamed the Aarons in a "Look-what-you-made-us-do?!" manner, never himself nor his deranged, destructive, toxic turbo troll gang!

DildoKKKobold

Holy cow, this thread took a life of its own. Next someone is going to figure out how to do a Lucas-wipe transition on the PC Engine!
AvatarDildoKKKobold.jpg
For a good time with the legendary DarkKobold, email: kylethomson@gmail.com
Dildos provided free of charge, no need to bring your own! :lol:
DoxPhile .com / chat
IMG

Arkhan Asylum

Quote from: DildoKKKobold on 12/13/2016, 01:01 AMHoly cow, this thread took a life of its own. Next someone is going to figure out how to do a Lucas-wipe transition on the PC Engine!
what one is that?

I made a few on MSX before settling on T&E soft's gridwipe because it's fuckin cool looking.
This "max-level forum psycho" (:lol:) destroyed TWO PC Engine groups in rage: one by Aaron Lambert on Facebook "Because Chris 'Shadowland' Runyon!," then the other by Aaron Nanto "Because Le NightWolve!" Him and PCE Aarons don't have a good track record together... Both times he blamed the Aarons in a "Look-what-you-made-us-do?!" manner, never himself nor his deranged, destructive, toxic turbo troll gang!