Author Topic: New thing I am making.  (Read 30085 times)

0 Members and 1 Guest are viewing this topic.

Offline Shockwave

  • good/evil
  • Founder Member
  • DBF Aficionado
  • ********
  • Posts: 17394
  • Karma: 498
  • evil/good
    • View Profile
    • My Homepage
Re: New thing I am making.
« Reply #40 on: July 13, 2007 »
Yes, that's a good idea Slippy, I'll add that in.
Shockwave ^ Codigos
Challenge Trophies Won:

Offline Stonemonkey

  • Pentium
  • *****
  • Posts: 1315
  • Karma: 96
    • View Profile
Re: New thing I am making.
« Reply #41 on: July 13, 2007 »
COuld you scale by x independantly? possibly making it look like they're rotating around each other.

Offline DragonSpirit

  • ZX 81
  • *
  • Posts: 13
  • Karma: 1
    • View Profile
Re: New thing I am making.
« Reply #42 on: July 14, 2007 »
First of all hi all.  i have been a member of these forums for a few months but not posted yet.  I have been trying to take in the different things, play with code and get a feel for the community etc.  I think the community here is great (unlike other sites that seem to have a goal in life to put everybody down) and there is lots of talent here.  Hopefully I will start contributing soon!!

Anyway, back to the post at hand, I love the effect of this intro but I have to agree that the black and white effect on the text does ruin it a little bit and maybe the fading idea would be better.

Keep up the excellent work Shockwave.  If i can master half of your talent in my freebasic programming I will be a happy man!!


Offline Shockwave

  • good/evil
  • Founder Member
  • DBF Aficionado
  • ********
  • Posts: 17394
  • Karma: 498
  • evil/good
    • View Profile
    • My Homepage
Re: New thing I am making.
« Reply #43 on: July 14, 2007 »
Hi Dragonspirit, it's nice to see you posting :) Feel free to get involved wherever you like, please do and thank you for your kind words about the place and my programs!

Stonemonkey, that's a nice idea about independantly scaline the letters to make them rotate.

I think that in the end I will go for a texture of some kind on the font though.

Just out of interest, the flickering method was made very cheaply, you can see two copies of each letter, I render the shadow and the foreground in the same loop in the same order all the time.

By having some sine and cos offset for the shadow to move it around the flickering is a mathematical side effect of this and the switch occurs as the letters move around. It's something I found by accident some years ago and I thought I'd give it a try to see if it worked. It doesn't suit the intro though so it's been binned!
Shockwave ^ Codigos
Challenge Trophies Won:

Offline DrewPee

  • I Toast Therefore I am
  • Pentium
  • *****
  • Posts: 563
  • Karma: 25
  • Eat Cheese - It's good for you!
    • View Profile
    • Retro Computer Museum
Re: New thing I am making.
« Reply #44 on: July 14, 2007 »
Looking cool shocky! Bloody Hell your checkerboard effect has come a long way!
Keep it up man looking fantastic!

DrewPee
DrewPee
aka Falcon of The Lost Boyz (Amiga)
Ex-Amiga Coder and Graphic Designer
Administrator of > www.retrocomputermuseum.co.uk

Offline Shockwave

  • good/evil
  • Founder Member
  • DBF Aficionado
  • ********
  • Posts: 17394
  • Karma: 498
  • evil/good
    • View Profile
    • My Homepage
Re: New thing I am making.
« Reply #45 on: July 16, 2007 »
Cheers drew :) I'm just hoping I haven't  :bfuck1: it up now because I added more stuff.

Here's the source code first;
Nb. It won't run as you need the font, however it is here so that you can have a look at it.

And attached to the post is a new exe.

Code: [Select]
'
'                                   New S!P Intro
'                                   By Shockwave!
'
'    Huge thanks to Rbraz I have used Tinyptc Ext and also his image code!
'    ---------------------------------------------------------------------
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' SETUP;
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
'#DEFINE PTC_WIN
    #INCLUDE "a256nickpal.bas"
    #INCLUDE "a256nickraw.bas"
    #INCLUDE "TINYPTC_EXT.BI"
'    #INCLUDE "TINYPTC.BI"
    #INCLUDE "WINDOWS.BI"   

    OPTION STATIC
    OPTION EXPLICIT

    CONST   XRES    =   800
    CONST   YRES    =   600

    DIM SHARED AS INTEGER   HALFX    =   XRES / 2
    DIM SHARED AS INTEGER   HALFY    =   YRES / 2
   
    DIM SHARED AS INTEGER LMARGIN = 80
    DIM SHARED AS INTEGER RMARGIN = 80
    DIM SHARED AS INTEGER TMARGIN = 80
    DIM SHARED AS INTEGER BMARGIN = 80


'-------------------------------------------------------------------------------
' INITIALISE LARGE FONT!!
'-------------------------------------------------------------------------------
    '--------------
    '--Image size--
    '--------------
   
    Const LfimgX = 1800
    Const LfimgY = 31
   

    Declare Sub LfDrawImage (byval imxpos as integer,byval imypos as integer,byval SX as integer,byval SY as integer,byval inter as double)

    Declare Sub LFLoadDataImage()   
    'Picture buffer
    Dim Shared LFimg_buffer( lfimgx * lfimgy ) as integer   
    'RGB color palette buffer
    Dim Shared LFimg_r(256), LFimg_g(256), LFimg_b(256) as short   
    LFLoadDataImage()
    DECLARE SUB LARGETEXT (BYVAL LTX AS INTEGER , BYVAL LTY AS INTEGER ,BYVAL LTS AS STRING,BYVAL inter AS double)

     
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' VARIABLE DECLARATION;
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
   
    DIM SHARED AS UINTEGER BUFFER ( XRES * YRES ):'       SCREEN BUFFER
    DIM SHARED AS INTEGER CHESS_RES = 20:'                CHESSFIELD DENSITY
   
    DIM SHARED AS DOUBLE  CXP ( CHESS_RES , CHESS_RES ):' CHESSFIELD X
    DIM SHARED AS DOUBLE  CYP ( CHESS_RES , CHESS_RES ):' CHESSFIELD Y
    DIM SHARED AS DOUBLE  CZP ( CHESS_RES , CHESS_RES ):' CHESSFIELD Z
    DIM SHARED AS DOUBLE BOARDOFFS:'                      CHESSFIELD SCROLL VAR
    DIM SHARED AS INTEGER CLICKS,CLICK:'                  USED TO CREATE PATTERN OFFSET
    CLICKS=0
   
    DIM SHARED AS INTEGER BPL ( 512,YRES*4 ):'            PALETTE (COPPERLIST)
    DIM SHARED AS DOUBLE  TIMER_SNAPSHOT:'                TO STORE A SNAPSHOT OF THE TIMER
    DIM SHARED AS DOUBLE  GADD:'                          USED TO MAKE SINE VALUES ETC
    DIM SHARED AS DOUBLE FUCKADD
    DIM SHARED AS INTEGER SCROLL (32*(YRES+32)):'         SCROLL BUFFER (HOLDS SCROLLTEXT IMAGE)
    DIM SHARED AS INTEGER SCROLLPOS=0:'                   SCROLL OFFSET VARIABLE
    dim shared AS INTEGER COPOFF :'                       COPPERLIST SCROLL OFFSET
    DIM SHARED AS INTEGER FPS,FPSS,YYY
    DIM SHARED AS DOUBLE OLDTIME
    DIM SHARED AS DOUBLE BORDER_CONTROL
   
    DIM SHARED AS STRING  MSG
    DIM SHARED AS DOUBLE TMPX(90)
    DIM SHARED AS DOUBLE TMPY(90)

    DIM SHARED AS DOUBLE STMPX(90)
    DIM SHARED AS DOUBLE STMPY(90)
   
    DIM SHARED AS DOUBLE  MDEL(90)

    DIM SHARED AS INTEGER CYCLE=1
   
    DIM SHARED AS INTEGER MMP=0

    MSG=MSG+"@@@@@@@@@@@@@@@"
    MSG=MSG+"@ STUNNING    @"
    MSG=MSG+"@        COOL @"
    MSG=MSG+"@ ADDICTED TO @"
    MSG=MSG+"@    OLDSKOOL @"
    MSG=MSG+"@@@@@@@@@@@@@@@"


    MSG=MSG+"THIS EFFECT WAS"
    MSG=MSG+"  VERY WIDELY  "
    MSG=MSG+" USED IN AMIGA "
    MSG=MSG+"DEMOS AND LOOKS"
    MSG=MSG+"  PRETTY COOL  "
    MSG=MSG+"    I THINK    "
   
    MSG=MSG+" SO THIS INTRO "
    MSG=MSG+"BEGINS TO SHAPE"
    MSG=MSG+"UP! AND  I ALSO"
    MSG=MSG+"HAVE  SOME NICE"
    MSG=MSG+"IDEAS  STILL TO"
    MSG=MSG+" ADD! -- SHOCK "   
   
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' SUBROUTINE DECLARATION;
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

    DECLARE SUB PREP_TEXT_GRID()
    DECLARE SUB GENERATE_TEXTURES():'                     TO CREATE TEXTURE MAPS
    DECLARE SUB SETBOARDPALETTE():'                       TO CREATE COPPERLIST FOR BOARD
    DECLARE SUB CHESS_SET ():'                            TO CREATE CHESSBOARD 3D OBJECT
    DECLARE SUB CHESS_DRAW():'                            TO DRAW CHESSBOARD
    DECLARE SUB TRIANGLE(BYVAL X1 AS INTEGER , BYVAL Y1 AS INTEGER, BYVAL X2 AS INTEGER , BYVAL Y2 AS INTEGER , BYVAL X3 AS INTEGER, BYVAL Y3 AS INTEGER , BYVAL TC AS INTEGER)
    DECLARE SUB DRAWSCROLL():'                            TO DRAW AND UPDATE THE SCROLLER
    declare sub brighten_buffer()
    DECLARE SUB ROTATE_BOARD()
    DECLARE SUB DRAW_MARGIN()
    DECLARE SUB WRITER_ON()
    DECLARE SUB WRITER_OFF()
   
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' OPEN SCREEN;
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

    PTC_ALLOWCLOSE(0)
    PTC_SETDIALOG(0,"RUN IN FULLSCREEN MODE?",0,0)
   
    IF (PTC_OPEN("((S!P))",XRES,YRES)=0) THEN
    END-1
    END IF 

'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' PALETTE AND OBJECT PRECALCULATION ;
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

    PREP_TEXT_GRID()
    CHESS_SET ()
    GENERATE_TEXTURES()
    SETBOARDPALETTE()

'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' MAIN LOOP;
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
OLDTIME = TIMER
BORDER_CONTROL=TIMER
WHILE(GETASYNCKEYSTATE(VK_ESCAPE)<>-32767)   
    GADD=GADD+1
    TIMER_SNAPSHOT=TIMER
   

    COPOFF=(HALFY*2)+1+((HALFY*2)*SIN(TIMER_SNAPSHOT))

            ROTATE_BOARD()
            CHESS_DRAW()


            IF CYCLE=0 THEN WRITER_OFF()
            IF CYCLE=1 THEN WRITER_ON()

            brighten_buffer()
            DRAW_MARGIN()

    PTC_UPDATE@BUFFER(0)
    ERASE BUFFER
    FPSS=FPSS+1
   
    IF TIMER-OLDTIME >=1 THEN
        FPS=FPSS
        PRINT FPS :' <- OUTPUT TO CONSOLE WINDOW ALT + TAB TO SEE.
        FPSS=0
        OLDTIME=TIMER
    END IF
   
WEND

'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' CLEAN UP AND EXIT;
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

PTC_CLOSE
END


'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' TEXTWRITER CONTROL PHASE 1 (LETTERS ON)
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

SUB WRITER_ON()
    DIM FLAGSET AS INTEGER
    DIM L AS INTEGER
    DIM VL AS DOUBLE
   
    FLAGSET=1
   
    FOR L=1 TO 90
       
        IF MDEL(L)>8 AND MDEL(L)<9 THEN
            TMPX(L) = HALFX
            '+(40*SIN(GADD/33))
            TMPY(L) = HALFY
            '+(40*SIN(GADD/25))
        END IF
       
        IF MDEL(L)<8 THEN
            VL=MDEL(L)
            IF VL<1 THEN VL=1
            LARGETEXT(TMPX(L),TMPY(L),MID (MSG,L+MMP,1),VL)
           
            IF TMPX(L) < STMPX(L) THEN TMPX(L) = TMPX(L) + ((STMPX(L) - TMPX(L))/20)
            IF TMPX(L) > STMPX(L) THEN TMPX(L) = TMPX(L) - ((TMPX(L) - STMPX(L))/20)           

            IF TMPY(L) < STMPY(L) THEN TMPY(L) = TMPY(L) + ((STMPY(L) - TMPY(L))/20)
            IF TMPY(L) > STMPY(L) THEN TMPY(L) = TMPY(L) - ((TMPY(L) - STMPY(L))/20)           

'            if TMPX(L) - STMPX(L) >-1 AND TMPX(L) - STMPX(L) < 1 THEN TMPX(L) = STMPX(L)
'            if TMPY(L) - STMPY(L) >-1 AND TMPY(L) - STMPY(L) < 1 THEN TMPY(L) = STMPY(L)

        END IF
   
        IF MDEL(L)>-50 THEN FLAGSET=0
   
        MDEL(L)=MDEL(L)-.2

       
       
       
    NEXT
    IF FLAGSET=1 THEN CYCLE=0
       
END SUB


'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' TEXTWRITER CONTROL PHASE 2 (LETTERS OFF)
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

SUB WRITER_OFF()
    DIM AS INTEGER FLAGSET = 1
    DIM L AS INTEGER
    DIM VL AS DOUBLE
    FOR L=1 TO 90

IF  MDEL(L)<8 THEN
   
            VL=MDEL(L)
            IF VL<1 THEN VL=1
            LARGETEXT(TMPX(L),TMPY(L),MID (MSG,L+MMP,1),VL)

END IF

        IF MDEL(L)>1 AND MDEL(L)<8 THEN

           
            IF TMPX(L) < HALFX THEN TMPX(L) = TMPX(L) + ((HALFX - TMPX(L))/20)
            IF TMPX(L) > HALFX THEN TMPX(L) = TMPX(L) - ((TMPX(L) - HALFX )/20)           

            IF TMPY(L) > HALFY THEN TMPY(L) = TMPY(L) - ((TMPY(L) -HALFY)/20)
            IF TMPY(L) < HALFY THEN TMPY(L) = TMPY(L) + ((HALFY - TMPY(L))/20)           


        END IF
   
        MDEL(L)=MDEL(L)+.2

        IF MDEL(L)<8 THEN FLAGSET=0
       
       
    NEXT
   
      IF FLAGSET=1 THEN
          CYCLE=1
          MMP=MMP+90
          IF MMP>(LEN(MSG)+90) THEN MMP=0
      END IF
     
END SUB

'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' CREATE TARGET POINTS FOR LETTERS OF TEXT WRITER.
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

SUB PREP_TEXT_GRID()
    DIM AS INTEGER XX,YY,L
    DIM AS INTEGER SSXX,SSYY
    DIM AS DOUBLE TXD
    SSXX=161
    SSYY=200
    TXD=150
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~   

    XX=SSXX
    YY=SSYY
   
    FOR L=1 TO 90
       
        STMPX(L) = XX
        STMPY(L) = YY
       
        MDEL(L)=TXD
        'MDEL(L)=50+(RND(1)*100)
        TXD=TXD-1.5
        XX=XX+32
        IF L MOD 15=0 THEN
            XX=SSXX
            YY=YY+36           
        END IF
    NEXT
   
END SUB

'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' THIS TAKES CARE OF THE BORDERS;
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

SUB DRAW_MARGIN()
   
   
    LMARGIN=80+38*SIN(FUCKADD/11)
    RMARGIN=80-38*SIN(FUCKADD/13)

    TMARGIN=80+38*SIN(FUCKADD/14)
    BMARGIN=80-38*SIN(FUCKADD/12)

IF TIMER-BORDER_CONTROL>1 THEN
    FUCKADD=FUCKADD+1
END IF
IF TIMER-BORDER_CONTROL>4 THEN BORDER_CONTROL = TIMER


    DIM  AS INTEGER Y , SLICE
    DIM AS UINTEGER MCL
    DIM AS UINTEGER PTR PP1,PP2,PP3,PP4
 
    PP1=@BUFFER(LMARGIN)
    PP2=@BUFFER(XRES-RMARGIN)
    PP3=@BUFFER(0)
    PP4=@BUFFER((XRES-RMARGIN)+1)   
   
    FOR Y=0 TO YRES-1
        MCL  = bpl(200,y+copoff)
        *PP1 = &HFFFFFF
        *PP2 = &HFFFFFF
        PP1+=XRES
        PP2+=XRES
       
    SLICE = LMARGIN
        asm
            mov eax, DWORD PTR[MCL]
            mov ecx, [slice]
            mov edi, [PP3]
            rep stosd
    end asm   

    SLICE = RMARGIN-1
        asm
            mov eax, DWORD PTR[MCL]
            mov ecx, [slice]
            mov edi, [PP4]
            rep stosd
    end asm   

    PP3+=XRES
    PP4+=XRES
    NEXT

'-------------------------------------------------------------------------
' TOP BITS
'-------------------------------------------------------------------------


    PP1=@BUFFER(LMARGIN)
    PP3=@BUFFER(0)
    PP4=@BUFFER((XRES-RMARGIN)+1)   
    FOR Y=0 TO TMARGIN-2
        IF Y<TMARGIN-2 THEN
            MCL  = bpl(300,y+copoff)
                    ELSE
            MCL  = &HFFFFFF
        END IF
        *PP1 = &HFFFFFF
        *PP2 = &HFFFFFF
        PP4+=XRES
        PP3+=XRES
        PP1+=XRES


    SLICE = LMARGIN
        asm
            mov eax, DWORD PTR[MCL]
            mov ecx, [slice]
            mov edi, [PP3]
            rep stosd
        end asm     



    SLICE = RMARGIN-1
        asm
            mov eax, DWORD PTR[MCL]
            mov ecx, [slice]
            mov edi, [PP4]
            rep stosd
        end asm     


        IF Y<TMARGIN-2 THEN
            MCL  = bpl(200,y+copoff)
                    ELSE
            MCL  = &hFFFFFF
        END IF
       
    SLICE = XRES-(LMARGIN+RMARGIN)
        asm
            mov eax, DWORD PTR[MCL]
            mov ecx, [slice]
            mov edi, [PP1]
            rep stosd
        end asm                 
    NEXT

'-------------------------------------------------------------------------
' BOTTOM BITS
'-------------------------------------------------------------------------

    PP1=@BUFFER(LMARGIN)
    PP3=@BUFFER(0)
    PP4=@BUFFER((XRES-RMARGIN)+1)   
    PP1 += XRES*(YRES-(BMARGIN+1))
    PP3 += XRES*(YRES-(BMARGIN+1))
    PP4 += XRES*(YRES-(BMARGIN+1))
    FOR Y=YRES-BMARGIN TO YRES-1
        IF Y>YRES-BMARGIN THEN
            MCL  = bpl(300,y+copoff)
                    ELSE
            MCL  = &hFFFFFF
        END IF
        *PP1 = &HFFFFFF
        *PP2 = &HFFFFFF
        PP4+=XRES
        PP3+=XRES
        PP1+=XRES


    SLICE = LMARGIN
        asm
            mov eax, DWORD PTR[MCL]
            mov ecx, [slice]
            mov edi, [PP3]
            rep stosd
        end asm     



    SLICE = RMARGIN-1
        asm
            mov eax, DWORD PTR[MCL]
            mov ecx, [slice]
            mov edi, [PP4]
            rep stosd
        end asm     


        IF Y>YRES-BMARGIN THEN
            MCL  = bpl(200,y+copoff)
                    ELSE
            MCL  = &hFFFFFF
        END IF
       
    SLICE = XRES-(LMARGIN+RMARGIN)
        asm
            mov eax, DWORD PTR[MCL]
            mov ecx, [slice]
            mov edi, [PP1]
            rep stosd
        end asm                 
    NEXT

END SUB

'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' ROTATES THE CHESSFIELD AROUND ONE AXIS;
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~


SUB ROTATE_BOARD()
       DIM AS DOUBLE RGADD
   DIM AS DOUBLE MO1,MO2,MMM,NNN
   DIM AS INTEGER X,Y
    RGADD=.02*SIN(GADD/237)
   
    MO1= COS(RGADD):' GENERATE MATRIX CONSTANT 1
    MO2= SIN(RGADD):' GENERATE MATRIX CONSTANT 2
   
FOR X=1 TO CHESS_RES
FOR Y=1 TO CHESS_RES
       
        '-----------------------------------------------------------------------
        ' ROTATE THE GRID
        '-----------------------------------------------------------------------
       
        NNN=CXP(X,Y)
        MMM=CYP(X,Y)
       
        CXP(X,Y) = MO1 * NNN - MO2 * MMM
        CYP(X,Y) = MO1 * MMM + MO2 * NNN
       

NEXT   
NEXT
END SUB

'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' THIS SUBROUTINE DRAWS THE SCROLLTEXT TO THE SCREEN LINEAR INTERPOLATED BETWEEN
' A SET OF POINTS DRAWN DOWN THE SCREEN TO "STRETCH" THE LETTERS.
' ALSO OF NOTE IS THE FACT THAT IT SCROLLS WITHOUT ACTUALLY SHIFTING ANY OF THE
' VALUES IN THE SCROLL BUFFER, IT SIMPLY USES AN OFFSET VARIABLE.
' THIS IS FAIRLY OPTIMISED, MORE CAN BE DONE.
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

SUB DRAWSCROLL()
   
    dim as integer CUNT,CUNT2
    CUNT = 40*SIN(TIMER_SNAPSHOT*3)
    CUNT2= 30*SIN(TIMER_SNAPSHOT*2)
    DIM AS INTEGER Y,X,x1,x2
    DIM AS DOUBLE SV
    DIM AS DOUBLE INTER,STRT
    FOR Y=0 TO YRES-1

        SV=((CUNT*COS((Y+TIMER_SNAPSHOT+GADD)/27))+(CUNT2*SIN((Y-GADD)/21)))

        X2=(HALFX+SV)+70:' GENERATE POINT B
        X1=(HALFX-SV)-70:' GENERATE POINT A
               
        STRT  =  SCROLLPOS*32:' PUT STRT AT CORRECT POINT IN SCROLL IMAGE
        INTER =  31 / (x2-x1):' WORK OUT INTERPOLATION VALUE
        '-----------------------------------------------------------------------
        ' DRAW ONE HORIZONTAL LINE OF THE SCROLL
        '-----------------------------------------------------------------------
        FOR X=X1 TO X2
            BUFFER(X+(Y*XRES)) = SCROLL(STRT)
            STRT=STRT+INTER
        NEXT
        '-----------------------------------------------------------------------
        ' ADVANCE SCROLL POINTER, IF AT END OF BANK - 1 LETTER, RESET IT :-p
        '-----------------------------------------------------------------------
        SCROLLPOS=SCROLLPOS+1
        IF SCROLLPOS>=YRES THEN SCROLLPOS=SCROLLPOS-YRES
    NEXT
   
        '-----------------------------------------------------------------------
        ' SCROLL WITHOUT COPYING ANY DATA :-P
        '-----------------------------------------------------------------------

        SCROLLPOS=SCROLLPOS+5
        IF SCROLLPOS>=YRES THEN SCROLLPOS=SCROLLPOS-YRES   
       
END SUB

'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' JUST MAKE A SIMPLE TEXTURE MAP AND STORE IT IN THE SCROLL BUFFER, LATER WE WILL
' USE THIS TO MAKE A NICER TEXTURE MAP TO COLOUR OUR SCROLL.
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

SUB GENERATE_TEXTURES()
    DIM AS INTEGER X,Y
    FOR Y=0 TO YRES+31
    FOR X=0 TO 32
        SCROLL(X+(Y*32)) = RGB((X*4) XOR (Y*4) , (X*4) XOR (Y*4),X XOR Y)

    NEXT
    NEXT
   
END SUB

'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' HERE WE CREATE THE COPPERLIST FOR THE CHESSBOARD.
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

SUB SETBOARDPALETTE()
    DIM AS INTEGER Z,Y
    DIM AS DOUBLE X
    X=0
    FOR Z=0 TO 512
       
        FOR Y=0 TO YRES*4
            BPL (Z,Y) = RGB(int(X+1+((X*SIN((Y+30)/120)))),int(X+1+((X*SIN((Y+50)/160)))),int(X+1+((X*SIN((Y+30)/170)))))

        NEXT
        IF X<125 THEN X=X+(Z/800)
    NEXT
   
END SUB

'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' SET UP CHESS BOARD;
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

SUB CHESS_SET()


    DIM AS INTEGER Z , Y
    DIM AS DOUBLE STRTZ , STRTY , CADD , AZP , AYP
   
    CADD  = ( 14000 / CHESS_RES )
   
    STRTZ =  .8
    STRTY =  -6500
   
    AZP = STRTZ
    AYP = STRTY
   
    FOR Z=1 TO CHESS_RES
       
        AYP=STRTY
       
        FOR Y=1 TO CHESS_RES
           
            CXP ( Y , Z ) = 850
            CYP ( Y , Z ) = AYP
            CZP ( Y , Z ) = AZP
           
        AYP = AYP + CADD           
       
        NEXT
       
        AZP = AZP + 1
       
    NEXT
   
END SUB


'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' DRAW CHESS BOARD.. THIS IS THE SLOW BIT!!!! NEEDS OPTIMISING.
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

SUB CHESS_DRAW()
   
        DIM AS INTEGER Z , Y , X
       

       
        DIM AS integer TX1 , TY1
        DIM AS integer TX2 , TY2
        DIM AS integer TX3 , TY3
        DIM AS integer TX4 , TY4
       
        DIM AS INTEGER CLICKED,CVLC
        CLICKED=CLICKS
        CVLC=(250-(BOARDOFFS*10))
       FOR Z=1 TO CHESS_RES -1
           CLICK=CLICKED
           CLICKED=CLICKED+1
           IF CLICKED>1 THEN CLICKED=0
        FOR Y=1 TO CHESS_RES -1
           
            TX1 =  ( CXP ( Y , Z ) / (CZP ( Y , Z )+BOARDOFFS) ) + HALFX           
            TY1 =  ( CYP ( Y , Z ) / (CZP ( Y , Z )+BOARDOFFS) ) + HALFY

            TX2 =  ( CXP ( Y+1 , Z ) / (CZP ( Y+1 , Z )+BOARDOFFS) ) + HALFX           
            TY2 =  ( CYP ( Y+1 , Z ) / (CZP ( Y+1 , Z )+BOARDOFFS) ) + HALFY

            TX3 =  ( CXP ( Y+1 , Z+1 ) / (CZP ( Y+1 , Z+1 )+BOARDOFFS) ) + HALFX           
            TY3 =  ( CYP ( Y+1 , Z+1 ) / (CZP ( Y+1 , Z+1 )+BOARDOFFS) ) + HALFY

            TX4 =  ( CXP ( Y , Z+1 ) / (CZP ( Y , Z+1 )+BOARDOFFS) ) + HALFX           
            TY4 =  ( CYP ( Y , Z+1 ) / (CZP ( Y , Z+1 )+BOARDOFFS) ) + HALFY

IF CLICK=1 THEN
            TRIANGLE(TX1,TY1,TX2,TY2,TX3,TY3 , CVLC*1.7 )
            TRIANGLE(TX1,TY1,TX4,TY4,TX3,TY3 , CVLC*1.7 )
           
else
            TRIANGLE(TX1,TY1,TX2,TY2,TX3,TY3 , CVLC*1.9 )
            TRIANGLE(TX1,TY1,TX4,TY4,TX3,TY3 , CVLC*1.9 )

END IF


            TX1 =  (-CXP ( Y , Z ) / (CZP ( Y , Z )+BOARDOFFS) ) + HALFX           
            TY1 =  (-CYP ( Y , Z ) / (CZP ( Y , Z )+BOARDOFFS) ) + HALFY

            TX2 =  (-CXP ( Y+1 , Z ) / (CZP ( Y+1 , Z )+BOARDOFFS) ) + HALFX           
            TY2 =  (-CYP ( Y+1 , Z ) / (CZP ( Y+1 , Z )+BOARDOFFS) ) + HALFY

            TX3 =  (-CXP ( Y+1 , Z+1 ) / (CZP ( Y+1 , Z+1 )+BOARDOFFS) ) + HALFX           
            TY3 =  (-CYP ( Y+1 , Z+1 ) / (CZP ( Y+1 , Z+1 )+BOARDOFFS) ) + HALFY

            TX4 =  (-CXP ( Y , Z+1 ) / (CZP ( Y , Z+1 )+BOARDOFFS) ) + HALFX           
            TY4 =  (-CYP ( Y , Z+1 ) / (CZP ( Y , Z+1 )+BOARDOFFS) ) + HALFY

IF CLICK=1 THEN
            TRIANGLE(TX1,TY1,TX2,TY2,TX3,TY3 , CVLC*1.7 )
            TRIANGLE(TX1,TY1,TX4,TY4,TX3,TY3 , CVLC*1.7 )
           
else
            TRIANGLE(TX1,TY1,TX2,TY2,TX3,TY3 , CVLC*1.9 )
            TRIANGLE(TX1,TY1,TX4,TY4,TX3,TY3 , CVLC*1.9 )

END IF

                CLICK=CLICK+1
                IF CLICK>1 THEN CLICK=0
           
        NEXT
        CVLC=CVLC-13
       NEXT

        DIM  AS UINTEGER PTR PP1,PP2

'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' MIRROR THE CHESSBOARD :-)
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

'FOR Y=0 to YRES-1
'   
'    PP1=@BUFFER((HALFX-40)+(XRES*Y))
'    PP2=@BUFFER((HALFX+40)+(XRES*Y))
'   
'    FOR X=1 TO HALFX-40
'        *PP1 = *PP2
'        PP1 -= 1
'        PP2 += 1
'    NEXT
'NEXT






        BOARDOFFS=BOARDOFFS+.1
        IF BOARDOFFS>1 THEN
            BOARDOFFS=BOARDOFFS-1
                CLICKS=CLICKS-1
                IF CLICKS<0 THEN CLICKS=1
        END IF
       
       
       
END SUB

SUB TRIANGLE(BYVAL X1 AS INTEGER , BYVAL Y1 AS INTEGER, BYVAL X2 AS INTEGER , BYVAL Y2 AS INTEGER , BYVAL X3 AS INTEGER, BYVAL Y3 AS INTEGER , BYVAL TC AS INTEGER)
'-------------------------------------------------------------------------
' FLAT TRIANGLE RENDERER WITH ASSEMBLY LANGUAGE RASTERISING BY SHOCKWAVE ^ DBF ^ S!P 2006.
'-------------------------------------------------------------------------
'-------------------------------------------------------------------------
' WE NEED TO SORT THESE POINTS INTO ORDER FROM TOP TO BOTTOM, AN EXCHANGE SORT IS OK.
' AS WE ONLY HAVE GOT 3 POINTS TO ARRANGE.
'-------------------------------------------------------------------------
DIM AS INTEGER TEMPX,TEMPY,LO,LI
                DIM AS INTEGER PX(3)
                DIM AS INTEGER PY(3)
                DIM TFLAG AS INTEGER
                dim pp as uinteger PTR
                DIM AS INTEGER IL1,IL2,SLICE,TTC
                TFLAG=0
        PX(1)= X1
        PX(2)= X2
        PX(3)= X3
       
        PY(1)= Y1
        PY(2)= Y2
        PY(3)= Y3

FOR LO = 1 TO 2
    FOR LI =1 TO 2     
        IF PY(LI+1) <= PY(LI) THEN
        TEMPX = PX(LI) : TEMPY = PY(LI)
        PX(LI) = PX(LI+1)
        PY(LI) = PY(LI+1)
        PX(LI+1) = TEMPX
        PY(LI+1) = TEMPY
        END IF   
    NEXT LI
NEXT LO
 
'   BOOT OUT INVISIBLE TRIANGLES!

    IF PX(1)<0 AND PX(2)<0  AND PX(3)< 0 THEN TFLAG=1
    IF PX(1)>XRES AND PX(2)>XRES  AND PX(3)>XRES THEN TFLAG=1
    IF PY(1)>YRES AND PY(2)>YRES  AND PY(3)>YRES THEN TFLAG=1
   
        DIM AS DOUBLE XP1,XP2:' SCREEN POSITIONS.
        DIM AS DOUBLE XI1,XI2:' INTERPOLATIONS.
       
'***
'*** REGULAR TRIANGLE (Y1<Y2 Y2<Y3)
'***

IF PY(1)<PY(2) AND PY(2)<PY(3) or (PY(2) = PY(3)) THEN
    TFLAG=1
XP1 = PX(1)
XP2 = PX(1)
XI1 = (PX(1)-PX(2)) / (PY(2) - PY(1))
XI2 = (PX(1)-PX(3)) / (PY(3) - PY(1))

FOR LO = PY(1) TO PY(2)-1
   
IF LO>=TMARGIN AND LO<YRES-BMARGIN THEN

    IF XP1<=XP2 THEN
        IL1=XP1
        IL2=XP2
    ELSE
        IL1=XP2
        IL2=XP1
    END IF
   
    IF IL2>XRES-RMARGIN THEN IL2=XRES-RMARGIN
    IF IL1<LMARGIN THEN IL1=LMARGIN

    SLICE = IL2-IL1
    IF SLICE>0 THEN
    TTC = BPL (TC,LO+COPOFF)
    PP = @BUFFER(IL1+(LO*XRES))   
    asm
        mov eax,dword ptr[TTC]
        mov ecx, [slice]
        mov edi, [PP]
        rep stosd
    end asm   
    END IF
   

END IF

XP1=XP1-XI1
XP2=XP2-XI2
NEXT

XI1 = (PX(2)-PX(3)) / (PY(3) - PY(2))
XP1 = PX(2)

FOR LO = PY(2) TO PY(3)
IF LO>=TMARGIN AND LO<YRES-BMARGIN THEN
    IF XP1<=XP2 THEN
        IL1=XP1
        IL2=XP2
    ELSE
        IL1=XP2
        IL2=XP1
    END IF

    IF IL2>XRES-RMARGIN THEN IL2=XRES-RMARGIN
    IF IL1<LMARGIN THEN IL1=LMARGIN

    SLICE = IL2-IL1
    IF SLICE>0 THEN
    TTC = BPL (TC,LO+COPOFF)
    PP = @BUFFER(IL1+(LO*XRES))   
    asm
        mov eax,dword ptr[TTC]
        mov ecx, [slice]
        mov edi, [PP]
        rep stosd
    end asm   
    END IF
END IF
XP1=XP1-XI1
XP2=XP2-XI2
NEXT

END IF


'***
'*** FLAT TOPPED TRIANGLE Y1=Y2
'***

IF TFLAG=0 AND PY(1) = PY(2) THEN
   
        TFLAG=1
        XP1 = PX(1)
        XP2 = PX(2)
        XI1 = (PX(1)-PX(3)) / (PY(3) - PY(1))
        XI2 = (PX(2)-PX(3)) / (PY(3) - PY(2))
FOR LO = PY(1) TO PY(3)
 IF LO>=TMARGIN AND LO<YRES-BMARGIN THEN
    IF XP1<=XP2 THEN
        IL1=XP1
        IL2=XP2
    ELSE
        IL1=XP2
        IL2=XP1
    END IF

    IF IL2>XRES-RMARGIN THEN IL2=XRES-RMARGIN
    IF IL1<LMARGIN THEN IL1=LMARGIN
   
    SLICE = IL2-IL1
    IF SLICE>0 THEN
    TTC = BPL (TC,LO+COPOFF)
    PP = @BUFFER(IL1+(LO*XRES))   
    asm
        mov eax,dword ptr[TTC]
        mov ecx, [slice]
        mov edi, [PP]
        rep stosd
    end asm   
    END IF
END IF
    XP1=XP1-XI1
    XP2=XP2-XI2

NEXT
END IF
END SUB


'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' BRIGHTEN BUFFER SUBROUTINE USING MMX INSTRUCTIONS! CHEERS STONEMONKEY!
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

sub brighten_buffer()
    asm
        pxor mm7, mm7
        mov ecx,XRES
        imul ecx,YRES
        lea eax,dword ptr[BUFFER]
        shl ecx,2   
        add ecx,eax
bright_loop:
            movd mm0,[eax]
            punpcklbw mm0, mm7
            psllw mm0,1
            packuswb mm0, mm7
            movd [eax],mm0
            add eax,4
            cmp eax,ecx
        jne bright_loop
        emms
    end asm
end sub

SUB LARGETEXT(BYVAL LTX AS INTEGER , BYVAL LTY AS INTEGER ,BYVAL LTS AS STRING,BYVAL inter AS double)
   
    DIM AS INTEGER A,MMM,NNN
'    lts=UCASE(LTS)
    FOR A=1 TO LEN(LTS)
    NNN=(ASC(MID(LTS,A,1))-33)
   
   
    IF NNN>63 THEN NNN=-1
    if nnn=0 then nnn=1
    MMM=NNN*31

    if nnn>0 then LFDRAWIMAGE( LTX,LTY, MMM , 0 , inter)
   
    LTX=LTX+31

    NEXT

END SUB





Sub LFLoadDataImage()
    dim i as integer
    'Loads Color palette
    for i = 0 to 255
         LFimg_r( i ) = a256nick.bmp.pal (i*3)'Red color
         LFimg_g( i ) = a256nick.bmp.pal (i*3+1)'Green color
         LFimg_b( i ) = a256nick.bmp.pal (i*3+2)'Blue color
         
         LFimg_r( i ) =(LFimg_r(i) Shl 16) Or (LFimg_g(i) Shl 8 )  Or LFimg_b(i)
         
    Next   
   
    for i = 1 to (LFimgx*LFimgy) - 1
         LFimg_buffer(i) = a256nick.bmp.raw (i)
    next 
       
End Sub



Sub LFDrawImage(byval xpos as integer,byval ypos as integer,byval SX as integer,byval SY as integer,byval inter as double)
    dim as integer x,y,pixel,mong,intx,inty,xxx,yyy,LAMER,MV
    dim as double XA
    dim as double YA
    dim as double mash
    DIM AS INTEGER FRX,FRY,one,two
    DIM CLLO AS INTEGER
    CLLO = ((8-INTER)*20)
   
   
    IF CLLO >250 THEN CLLO=250
    two = rgb(CLLO,CLLO,CLLO)
    one = rgb(CLLO/4,CLLO/4,CLLO/3)
    FRX=1
    FRY=1
   
    mash =  (32-(32 / INTER))/2
   
        xpos=xpos+mash
        ypos=ypos+mash
       
    LAMER = RGB(240,240,240)
    MV=0
    xxx=xpos
    yyy=0
    XA = SX
    YA = SY
    x=sx
    y=sy
if inter>1 then   
    WHILE YA<30

    Y=INT(YA)
    YA=YA+INTER
        MV=0       
        XA=SX
        WHILE XA<SX+31
        X=INT(XA)
        XA=XA+INTER
     
            pixel = LFimg_buffer(x+(y*lfimgx))           
            mong = (LFimg_r(pixel) )           
           
                intx = xxx
               
                inty = yyy+ypos
               
                if intX > 0  AND intX<XRES AND MONG<>&H000000 then
                Buffer( (intX  +FRX)+((intY+FRY) * XRES  )) = ONE
                Buffer( intX  +(intY * XRES  )) = TWO
               

               
               
            END IF
           
            xxx=xxx+1
            mv=mv+1

        WEND
            yyy=yyy+1
            xxx=xpos

    WEND
else
   
    for Y = 0 to 30
   
   
        MV=0       
   
       
       
        for X = SX+1 to SX+31
           
            pixel = LFimg_buffer(x+(y*lfimgx))           
            mong = (LFimg_r(pixel) )           
           
                intx = xxx
               
                inty = yyy+ypos
               
                if intX > 0  AND intX<XRES AND MONG<>&H000000 then
               
                Buffer( (intX  +FRX)+((intY+FRY) * XRES  )) = ONE
                Buffer( intX  +(intY * XRES  )) = TWO
               

               
               
            END IF
           
            xxx=xxx+1
            mv=mv+1
        next
       
            yyy=yyy+1
            xxx=xpos
    next
   
end if

End Sub

A few things that I am puzzling over now are still the final resolution, where can I fit a logo, I am also unhappy with the font too, something needs to be done to make it fit in better.
Shockwave ^ Codigos
Challenge Trophies Won:

Offline benny!

  • Senior Member
  • DBF Aficionado
  • ********
  • Posts: 4384
  • Karma: 228
  • in this place forever!
    • View Profile
    • bennyschuetz.com - mycroBlog
Re: New thing I am making.
« Reply #46 on: July 16, 2007 »
@SW:

Unbelievable ... that design looks outstanding and like a premium cracktro. Really
like the idea of the moving squares in the corner. Outstanding work, mate !!!
[ mycroBLOG - POUET :: whatever keeps us longing - for another breath of air - is getting rare ]

Challenge Trophies Won:

Offline Stonemonkey

  • Pentium
  • *****
  • Posts: 1315
  • Karma: 96
    • View Profile
Re: New thing I am making.
« Reply #47 on: July 21, 2007 »
Looking good Shockwave, nice work.

Offline Shockwave

  • good/evil
  • Founder Member
  • DBF Aficionado
  • ********
  • Posts: 17394
  • Karma: 498
  • evil/good
    • View Profile
    • My Homepage
Re: New thing I am making.
« Reply #48 on: July 21, 2007 »
Thanks :) I hope to do a little bit more with this today as I had a half day at work and finally have a few hours of spare time (not to mention half a bottle of wine) so with some luck I'll post an update later on with some source too for the peeps that are following this little intros development.

Also it must be said that it wouldn't look as nice and shiny as it does without a little mmx routine by stonemonkey.
Shockwave ^ Codigos
Challenge Trophies Won:

Offline Hotshot

  • DBF Aficionado
  • ******
  • Posts: 2114
  • Karma: 91
    • View Profile
Re: New thing I am making.
« Reply #49 on: July 21, 2007 »
wow that is excellent......keep it good work up

Offline Shockwave

  • good/evil
  • Founder Member
  • DBF Aficionado
  • ********
  • Posts: 17394
  • Karma: 498
  • evil/good
    • View Profile
    • My Homepage
Re: New thing I am making.
« Reply #50 on: July 21, 2007 »
I wish I could do things right third time :) I know first and second time will never be on the cards, third time would do.

I've been playing with the borders, yet again! I was looking at the deforming borders and wondered what the hell I'd done them for, it was impossible to think of an effect that would suit it.

In the end I forced myself to realise that is was an excuse.
It was an excuse to run the intro in 800 X 600 and because it is software rendered, I have to draw every single fucking pixel.

Effectively all I did was letterbox the display so the intro definately won't be going back there.

I spoke to some of my friends, among other things, lightning between the planes was suggested, as was glenze cubes and cute stars..

So I killed off the borders.
I put the board full screen.
Realised that I missed the borders so modified the triangle code slightly to shade the top and bottom parts of the screen and finally added some stars.

I am happier with it but still not happy.
The font needs to be changed to a nicer one, also the stars are not in order at the moment so they need to be done.

Probably I won't use a logo on this screen, I'll grab a splash screen off one of S!P's artists instead :)

Anyway, attached is a zip containing the exe and sources.
Uses ptc_ext (thanks rbraz).
Shockwave ^ Codigos
Challenge Trophies Won:

Offline p01

  • Atari ST
  • ***
  • Posts: 158
  • Karma: 51
    • View Profile
    • www.p01.org
Re: New thing I am making.
« Reply #51 on: July 21, 2007 »
Really nice.

Could you add a timer so that the animation runs at the same speed on any configuration.

IMHO the text should appear from top to bottom and 5 spikes starts would look better.

Offline Rbz

  • Founder Member
  • DBF Aficionado
  • ********
  • Posts: 2750
  • Karma: 493
    • View Profile
    • http://www.rbraz.com/
Re: New thing I am making.
« Reply #52 on: July 21, 2007 »
Yeah, much more nice now, and yes you need better font...
Challenge Trophies Won:

Offline Stonemonkey

  • Pentium
  • *****
  • Posts: 1315
  • Karma: 96
    • View Profile
Re: New thing I am making.
« Reply #53 on: July 21, 2007 »
No idea how easy/difficult it would be but some sort of smoothing of the font using alpha around the curved edges would be nice. But really no idea how.

Offline Tetra

  • DBF Aficionado
  • ******
  • Posts: 2532
  • Karma: 83
  • Pirate Monkey!
    • View Profile
Re: New thing I am making.
« Reply #54 on: July 21, 2007 »
Sweet!

I like how that is looking :) nice colors and shading too
Challenge Trophies Won:

Offline benny!

  • Senior Member
  • DBF Aficionado
  • ********
  • Posts: 4384
  • Karma: 228
  • in this place forever!
    • View Profile
    • bennyschuetz.com - mycroBlog
Re: New thing I am making.
« Reply #55 on: July 22, 2007 »
Awesome stuff Shockie ... I really like the stars and the chessboard movement now.
[ mycroBLOG - POUET :: whatever keeps us longing - for another breath of air - is getting rare ]

Challenge Trophies Won:

Offline taj

  • Bytes hurt
  • DBF Aficionado
  • ******
  • Posts: 4810
  • Karma: 189
  • Scene there, done that.
    • View Profile
Re: New thing I am making.
« Reply #56 on: July 22, 2007 »
Shocks,

the stars are great , I wouldn't waste time sorting them you cant tell on a first look. I'd like the viewpoint to move more get closer to checker board then away again. But perhaps you hardcoded the angle for speed? Honestly I preferred the bouncing borders but being no artist, I'm probably wrong. Its just I've seen far too many "wide angle cinema scope" borders.

It looks great in any case.

Chris
Challenge Trophies Won:

Offline Shockwave

  • good/evil
  • Founder Member
  • DBF Aficionado
  • ********
  • Posts: 17394
  • Karma: 498
  • evil/good
    • View Profile
    • My Homepage
Re: New thing I am making.
« Reply #57 on: July 22, 2007 »
Wow! Lots of suggestions, thank you everybody I wasn't expecting them! This was just my ramblings as this project progresses slowly...

I will be adding a few of those ideas, you can be sure of that and I really appreciate the testing :)
Shockwave ^ Codigos
Challenge Trophies Won:

Offline Shockwave

  • good/evil
  • Founder Member
  • DBF Aficionado
  • ********
  • Posts: 17394
  • Karma: 498
  • evil/good
    • View Profile
    • My Homepage
Re: New thing I am making.
« Reply #58 on: July 22, 2007 »
Here it is with some of those great suggestions implimented! Thanks so much :)
Shockwave ^ Codigos
Challenge Trophies Won:

Offline Stonemonkey

  • Pentium
  • *****
  • Posts: 1315
  • Karma: 96
    • View Profile
Re: New thing I am making.
« Reply #59 on: July 22, 2007 »
Looking better now, and you did the thing with the alpha edges on the font and it's looking less blocky but something strange is happening when the background is bright, the alpha edges show up a bit.