Cross-Fading

                    ÕÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍ͸
                    ³         W E L C O M E         ³
                    ³  To the VGA Trainer Program   ³ ³
                    ³              By               ³ ³
                    ³      DENTHOR of ASPHYXIA      ³ ³ ³
                    ÔÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍ; ³ ³
                      ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÙ ³
                        ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÙ

                            --==[ PART 11 ]==--

 =-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=
 þ Introduction

 Hello again everybody!

 The reason _this_ one is delayed (every single trainer has been so far ;))
 is mainly due to a birthday (my 19th), and numerous tests at the
 university (ugh!).  But anyway, here it is. The sample program this time
 is on cross-fading. The reason for this is that many people have
 commented that I should be moving over to a few basic demo effects now
 that we have most of the basics of VGA programming.  I was also thinking
 of either doing sound in a future version of this trainer, or starting a
 separate "ASPHYXIA Sound Tutorial" series. Comments?

 One major difference between this trainer and previous ones is that I am
 including binary files (pictures in this case). This means that it will
 not be available in the message bases of selected boards anymore, and it
 must be obtained from the file base.  Notice will however be given of
 it's existence in the message base.

 Asphyxia has formalised things a bit, and we now have a few official
 distribution sites for all our demos and trainers. If you would like
 your BBS to become a distribution site, please email me at
 smith9@batis.bis.und.ac.za and I will send you the necessary info.

 If you would like to contact me, or the team, there are many ways you
 can do it : 1) Write a message to Grant Smith/Denthor/Asphyxia in private mail
                   on the ASPHYXIA BBS.
             2) Write to Denthor, EzE, Goth, Fubar or Nobody on Connectix.
             3) Write to :  Grant Smith
                            P.O.Box 270 Kloof
                            3640
                            Natal
                            South Africa
             4) Call me (Grant Smith) at (031) 73 2129 (leave a message if you
                   call during varsity). Call +27-31-73-2129 if you call
                   from outside South Africa. (It's YOUR phone bill ;-))
             5) Write to smith9@batis.bis.und.ac.za in E-Mail.

 NB : If you are a representative of a company or BBS, and want ASPHYXIA
        to do you a demo, leave mail to me; we can discuss it.
 NNB : If you have done/attempted a demo, SEND IT TO ME! We are feeling
         quite lonely and want to meet/help out/exchange code with other demo
         groups. What do you have to lose? Leave a message here and we can work
         out how to transfer it. We really want to hear from you!

 =-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=
 þ What is a "Crossfade"?

 This is a simple question. When you are watching a TV program, you will
 often see one picture on the screen, which slowly fades to a new
 picture, with the new picture becoming more and more prominent and the
 old one becoming less and less prominent. This is a crossfade. Easy huh?

 Perhaps, but it is not that easy to code on a computer...

 In most demos, there is a crossfade of two colors, black and white, for
 example : The words 'MYDEMOTEAM' appears in large with letters, then
 crossfades to 'PRESENTS' in large white letters.

 I decided to allow the programmer to have a bit of color to his
 crossfade, and the sample program can handle a many color crossfade.

 =-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=
 þ How does a crossfade work?

 Here comes the clever bit.

 To do a crossfade, we load in two pictures, FROM and TO. Then, for every
 pixel in which they are different, put a new pixel in a third screen.

 For example, wherever there is pixel color 9 on screen 1 and pixel color
 45 on screen 2, put pixel color 1 on the third screen. You then repeat
 this for all combinations of pixels on screen one and two, and put the
 results into screen 3. Here it is in ascii ...

   Screen 1     Screen 2     Screen 3
    .1...        .3...        .1...
    .....        ..2..        ..2..
    ...8.    +   ...1.    =   ...3.
    .1...        ....2        .4..2

 Note how the values on screen 3 are sequential? We keep a count for
 this... The two "2"'s on screen 3 are identical, so we do not use a new
 color for it...

 We also keep to pallettes ... source and dest.

 For the above example source[1] would be the pallette of 1 in screen 1,
 and dest[1] would be the pallette of 3 in screen 2 (Note that screen 1
 and screen 2 have different pallettes)

 When we are finished with the picture, we flip screen 3 to the vga and
 do the following : move the pallette from source to dest or vice versa.
 Thats it. No fancy screen manipulations for the crossfade, we just
 change the pallette. Cool, huh? It also means that you can be doing fun
 stuff in the foreground with unused pallette colors without your program
 executing at two frames per second ;)

 The sample program is fully documented, and you shouldn't have a problem
 deciphering it... If you ever use this effect in a demo or game, greet
 me! :-)

 =-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=
 þ Problems with crossfades

 The main problem with crossfading is this : there may only be 256 colors
 on screen 3, in other words, only 256 combinations of colors.  In the
 sample program, if you load up two pics with more then 256 combinations,
 the program gives an error message and exits to dos. To sort this
 problem out, you can do two things : reduce the number of places where
 the two pictures intersect, or squeeze down the pallette, using
 Autodesk Animators "SQUEEZE" command. This reduces the number of colors
 used by the picture, and therefore reduces the number of combinations.
 The picture does however lose a bit of quality.

 The second problem with crossfading is this : It hogs most of the
 colors. Whatever you want to do in the foreground, make sure you do it
 with as few colors as possible.

 =-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=
 þ In closing

 So, what do you think? Should I continue with demo effects, or should I
 find more basic things to do? Perhaps I should stop and just do sound
 coding from now on? It is up to you, so leave me mail.

 You will notice that the sample program can load in any .CEL files, you
 needn't be restricted by the ones I have given you. Try crossfading a
 few of your own pictures and see how it turns out. The picture of the
 robot was draw by Fubar for our demo Psycho Neurosis, and I then
 squeezed down the pallette somewhat in order for the crossfade to work.
 The word "ASPHYXIA" was drawn by me, also in Autodesk Animator.

 Oh well, I had better get this off quickly, today is the last time for
 the next few days that I can get on to the Net. I will also be voting
 tomorrow! If I see a CNN camera, I'll wave (Thats me, the one on the
 left in the red shirt! ;-))  The next trainer will be coming from the
 New South Africa (TM)

 See you next time!
  - Denthor
      - 9:16, 26 April, 1994

 PS. Does anyone in Holland with net access want to act as a courier
 between myself and the Accidental Connection BBS? Please leave me mail
 at smith9@batis.bis.und.ac.za ....

 The following are official ASPHYXIA distribution sites :

 ÉÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍËÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍËÍÍÍÍÍ»
 ºBBS Name                  ºTelephone No.   ºOpen º
 ÌÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÎÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÎÍÍÍÍ͹
 ºASPHYXIA BBS #1           º+27-31-765-5312 ºALL  º
 ºASPHYXIA BBS #2           º+27-31-765-6293 ºALL  º
 ºConnectix BBS             º+27-31-266-9992 ºALL  º
 ºPOP!                      º+27-12-661-1257 ºALL  º
 ºPure Surf BBS             º+27-31-561-5943 ºA/H  º
 ºWasted Image              º407-838-4525    ºALL  º
 ÈÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÊÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÊÍÍÍÍͼ

 Leave me mail if you want to become an official Asphyxia BBS
 distribution site.

 (I will find out the country code for Wasted Image later...)

 Unit GFX2;

 INTERFACE

 USES crt;
 CONST VGA = $A000;

 TYPE Virtual = Array [1..64000] of byte;  { The size of our Virtual Screen }
      VirtPtr = ^Virtual;                  { Pointer to the virtual screen }

 VAR Virscr : VirtPtr;                     { Our first Virtual screen }
     Vaddr  : word;                        { The segment of our virtual screen}

 Procedure SetMCGA;
    { This procedure gets you into 320x200x256 mode. }
 Procedure SetText;
    { This procedure returns you to text mode.  }
 Procedure Cls (Where:word;Col : Byte);
    { This clears the screen to the specified color }
 Procedure SetUpVirtual;
    { This sets up the memory needed for the virtual screen }
 Procedure ShutDown;
    { This frees the memory used by the virtual screen }
 procedure flip(source,dest:Word);
    { This copies the entire screen at "source" to destination }
 Procedure Pal(Col,R,G,B : Byte);
    { This sets the Red, Green and Blue values of a certain color }
 Procedure GetPal(Col : Byte; Var R,G,B : Byte);
   { This gets the Red, Green and Blue values of a certain color }
 procedure WaitRetrace;
    {  This waits for a vertical retrace to reduce snow on the screen }
 Procedure Hline (x1,x2,y:word;col:byte;where:word);
    { This draws a horizontal line from x1 to x2 on line y in color col }
 Procedure Line(a,b,c,d:integer;col:byte;where:word);
   { This draws a solid line from a,b to c,d in colour col }
 Procedure DrawPoly(x1,y1,x2,y2,x3,y3,x4,y4:integer;color:byte;where:word);
    { This draw a polygon with 4 points at x1,y1 , x2,y2 , x3,y3 , x4,y4
      in color col }
 Function rad (theta : real) : real;
    {  This calculates the degrees of an angle }
 Procedure Putpixel (X,Y : Integer; Col : Byte; where:word);
    { This puts a pixel on the screen by writing directly to memory. }
 Function Getpixel (X,Y : Integer; where:word) :Byte;
    { This gets the pixel on the screen by reading directly to memory. }
 Procedure LoadCEL (FileName :  string; ScrPtr : pointer);
   { This loads the cel 'filename' into the pointer scrptr }

 IMPLEMENTATION

 {ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ}
 Procedure SetMCGA;  { This procedure gets you into 320x200x256 mode. }
 BEGIN
   asm
      mov        ax,0013h
      int        10h
   end;
 END;

 {ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ}
 Procedure SetText;  { This procedure returns you to text mode.  }
 BEGIN
   asm
      mov        ax,0003h
      int        10h
   end;
 END;

 {ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ}
 Procedure Cls (Where:word;Col : Byte); assembler;
    { This clears the screen to the specified color }
 asm
    push    es
    mov     cx, 32000;
    mov     es,[where]
    xor     di,di
    mov     al,[col]
    mov     ah,al
    rep     stosw
    pop     es
 End;

 {ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ}
 Procedure SetUpVirtual;
    { This sets up the memory needed for the virtual screen }
 BEGIN
   GetMem (VirScr,64000);
   vaddr := seg (virscr^);
 END;

 {ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ}
 Procedure ShutDown;
    { This frees the memory used by the virtual screen }
 BEGIN
   FreeMem (VirScr,64000);
 END;

 {ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ}
 procedure flip(source,dest:Word); assembler;
   { This copies the entire screen at "source" to destination }
 asm
   push    ds
   mov     ax, [Dest]
   mov     es, ax
   mov     ax, [Source]
   mov     ds, ax
   xor     si, si
   xor     di, di
   mov     cx, 32000
   rep     movsw
   pop     ds
 end;

 {ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ}
 Procedure Pal(Col,R,G,B : Byte); assembler;
   { This sets the Red, Green and Blue values of a certain color }
 asm
    mov    dx,3c8h
    mov    al,[col]
    out    dx,al
    inc    dx
    mov    al,[r]
    out    dx,al
    mov    al,[g]
    out    dx,al
    mov    al,[b]
    out    dx,al
 end;

 {ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ}
 Procedure GetPal(Col : Byte; Var R,G,B : Byte);
   { This gets the Red, Green and Blue values of a certain color }
 Var
    rr,gg,bb : Byte;
 Begin
    asm
       mov    dx,3c7h
       mov    al,col
       out    dx,al

       add    dx,2

       in     al,dx
       mov    [rr],al
       in     al,dx
       mov    [gg],al
       in     al,dx
       mov    [bb],al
    end;
    r := rr;
    g := gg;
    b := bb;
 end;

 {ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ}
 procedure WaitRetrace; assembler;
   {  This waits for a vertical retrace to reduce snow on the screen }
 label
   l1, l2;
 asm
     mov dx,3DAh
 l1:
     in al,dx
     and al,08h
     jnz l1
 l2:
     in al,dx
     and al,08h
     jz  l2
 end;

 {ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ}
 Procedure Hline (x1,x2,y:word;col:byte;where:word); assembler;
   { This draws a horizontal line from x1 to x2 on line y in color col }
 asm
   mov   ax,where
   mov   es,ax
   mov   ax,y
   mov   di,ax
   shl   ax,8
   shl   di,6
   add   di,ax
   add   di,x1

   mov   al,col
   mov   ah,al
   mov   cx,x2
   sub   cx,x1
   shr   cx,1
   jnc   @start
   stosb
 @Start :
   rep   stosw
 end;

 {ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ}
 Procedure Line(a,b,c,d:integer;col:byte;where:word);
   { This draws a solid line from a,b to c,d in colour col }
   function sgn(a:real):integer;
   begin
        if a>0 then sgn:=+1;
        if a<0 then sgn:=-1;
        if a=0 then sgn:=0;
   end;
 var i,s,d1x,d1y,d2x,d2y,u,v,m,n:integer;
 begin
      u:= c - a;
      v:= d - b;
      d1x:= SGN(u);
      d1y:= SGN(v);
      d2x:= SGN(u);
      d2y:= 0;
      m:= ABS(u);
      n := ABS(v);
      IF NOT (M>N) then
      BEGIN
           d2x := 0 ;
           d2y := SGN(v);
           m := ABS(v);
           n := ABS(u);
      END;
      s := m shr 1;
      FOR i := 0 TO m DO
      BEGIN
           putpixel(a,b,col,where);
           s := s + n;
           IF not (smxy then mxy:=y2;
   if y3mxy then mxy:=y3;    { Choose the min y mny and max y mxy }
   if y4mxy then mxy:=y4;

   if mny<0 then mny:=0;
   if mxy>199 then mxy:=199;
   if mny>199 then exit;
   if mxy<0 then exit;        { Verticle range checking }

   mul1:=x1-x4; div1:=y1-y4;
   mul2:=x2-x1; div2:=y2-y1;
   mul3:=x3-x2; div3:=y3-y2;
   mul4:=x4-x3; div4:=y4-y3;  { Constansts needed for intersection calc }

   for yc:=mny to mxy do
     begin
       mnx:=320;
       mxx:=-1;
       if (y4>=yc) or (y1>=yc) then
         if (y4<=yc) or (y1<=yc) then   { Check that yc is between y1 and y4 }
           if not(y4=y1) then
             begin
               x:=(yc-y4)*mul1 div div1+x4; { Point of intersection on x axis }
               if xmxx then
                 mxx:=x;       { Set point as start or end of horiz line }
             end;
       if (y1>=yc) or (y2>=yc) then
         if (y1<=yc) or (y2<=yc) then   { Check that yc is between y1 and y2 }
           if not(y1=y2) then
             begin
               x:=(yc-y1)*mul2 div div2+x1; { Point of intersection on x axis }
               if xmxx then
                 mxx:=x;       { Set point as start or end of horiz line }
             end;
       if (y2>=yc) or (y3>=yc) then
         if (y2<=yc) or (y3<=yc) then   { Check that yc is between y2 and y3 }
           if not(y2=y3) then
             begin
               x:=(yc-y2)*mul3 div div3+x2; { Point of intersection on x axis }
               if xmxx then
                 mxx:=x;       { Set point as start or end of horiz line }
             end;
       if (y3>=yc) or (y4>=yc) then
         if (y3<=yc) or (y4<=yc) then   { Check that yc is between y3 and y4 }
           if not(y3=y4) then
             begin
               x:=(yc-y3)*mul4 div div4+x3; { Point of intersection on x axis }
               if xmxx then
                 mxx:=x;       { Set point as start or end of horiz line }
             end;
       if mnx<0 then
         mnx:=0;
       if mxx>319 then
         mxx:=319;          { Range checking on horizontal line }
       if mnx<=mxx then
         hline (mnx,mxx,yc,color,where);   { Draw the horizontal line }
     end;
   end;

 {ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ}
 Function rad (theta : real) : real;
   {  This calculates the degrees of an angle }
 BEGIN
   rad := theta * pi / 180
 END;

 {ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ}
 Procedure Putpixel (X,Y : Integer; Col : Byte; where:word); assembler;
   { This puts a pixel on the screen by writing directly to memory. }
 Asm
   mov     ax,[where]
   mov     es,ax
   mov     bx,[X]
   mov     dx,[Y]
   mov     di,bx
   mov     bx, dx                  {; bx = dx}
   shl     dx, 8
   shl     bx, 6
   add     dx, bx                  {; dx = dx + bx (ie y*320)}
   add     di, dx                  {; finalise location}
   mov     al, [Col]
   stosb
 End;

 {ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ}
 Function Getpixel (X,Y : Integer; where:word):byte; assembler;
   { This puts a pixel on the screen by writing directly to memory. }
 Asm
   mov     ax,[where]
   mov     es,ax
   mov     bx,[X]
   mov     dx,[Y]
   mov     di,bx
   mov     bx, dx                  {; bx = dx}
   shl     dx, 8
   shl     bx, 6
   add     dx, bx                  {; dx = dx + bx (ie y*320)}
   add     di, dx                  {; finalise location}
   mov     al, es:[di]
 End;

 {ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ}
 Procedure LoadCEL (FileName :  string; ScrPtr : pointer);
   { This loads the cel 'filename' into the pointer scrptr }
 var
   Fil : file;
   Buf : array [1..1024] of byte;
   BlocksRead, Count : word;
 begin
   assign (Fil, FileName);
   reset (Fil, 1);
   BlockRead (Fil, Buf, 800);    { Read and ignore the 800 byte header }
   Count := 0; BlocksRead := $FFFF;
   while (not eof (Fil)) and (BlocksRead <> 0) do begin
     BlockRead (Fil, mem [seg (ScrPtr^): ofs (ScrPtr^) + Count], 1024, BlocksRead);
     Count := Count + 1024;
   end;
   close (Fil);
 end;

 BEGIN
 END.{$X+}
 USES GFX2,crt;  { Please use the GFX2 unit from now on! The GFX unit had
                   quite a big bug in it, and less routines... }

 Type Pallette = Array [0..255,1..3] of byte;

 VAR source,dest:Pallette;
     VirScr2 : VirtPtr;                     { Our second Virtual screen }
     Vaddr2 : Word;                      { The segment of our 2nd virt. screen}
     dir:boolean;     { Fade up or fade down? }
     loop1:integer;

 {ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ}
 Procedure LoadCELPal (FileName : String; Var Palette : Pallette);
   { This loads in the pallette of the .CEL file into the variable Palette }
 Var
   Fil : file;
 Begin
   Assign (Fil, FileName);
   Reset (Fil, 1);
   Seek(Fil,32);
   BlockRead (Fil, Palette, 768);
   Close (Fil);
 End;

 {ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ}
 Procedure Init;
   { We get memory for our pointers here }
 BEGIN
   fillchar (source,sizeof(source),0);
   fillchar (dest,sizeof(dest),0);
   GetMem (VirScr2,64000);
   vaddr2 := seg (virscr2^);
 END;

 {ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ}
 Procedure SetItUp;
   { We define our third screen here }
 VAR loop1,loop2,loop3:integer;
     pal1,pal2:pallette;
     change:boolean;
     where:integer;
     r,g,b,r1,g1,b1:byte;
 BEGIN
   cls (vaddr2,0);

   For loop1:=0 to 255 do
     pal (loop1,0,0,0);

   loadcel ('to.cel',virscr);
   loadcelpal ('to.cel',pal2);
   flip (vaddr,vga);
   loadcel ('from.cel',virscr);
   loadcelpal ('from.cel',pal1);

   where:=0;

   For loop1:=0 to 319 do
     for loop2:=0 to 199 do BEGIN
       if (getpixel(loop1,loop2,vaddr)<>0) or (getpixel (loop1,loop2,vga)<>0) then BEGIN
         change:=false;
         r:=pal1[getpixel(loop1,loop2,vaddr),1];
         g:=pal1[getpixel(loop1,loop2,vaddr),2];
         b:=pal1[getpixel(loop1,loop2,vaddr),3];
         r1:=pal2[getpixel(loop1,loop2,vga),1];
         g1:=pal2[getpixel(loop1,loop2,vga),2];
         b1:=pal2[getpixel(loop1,loop2,vga),3];

         for loop3:=0 to where do
           if (source[loop3,1]=r) and (source[loop3,2]=g) and (source[loop3,3]=b) and
              (dest[loop3,1]=r1) and (dest[loop3,2]=g1) and (dest[loop3,3]=b1) then BEGIN
              putpixel (loop1,loop2,loop3,vaddr2);
              change:=TRUE;
           END;
           { Here we check that this combination hasn't occured before. If it
             has, put the appropriate pixel onto the third screen (vaddr2) }

         if not (change) then BEGIN
           inc (where);
           if where=256 then BEGIN
             settext;
             writeln ('Pictures have too many colors! Squeeze then retry!');
             Halt;
             { There were too many combinations of colors. Alter picture and
               then retry }
           END;
           putpixel(loop1,loop2,where,vaddr2);
           source[where,1]:=pal1[getpixel(loop1,loop2,vaddr),1];
           source[where,2]:=pal1[getpixel(loop1,loop2,vaddr),2];
           source[where,3]:=pal1[getpixel(loop1,loop2,vaddr),3];
           dest[where,1]:=pal2[getpixel(loop1,loop2,vga),1];
           dest[where,2]:=pal2[getpixel(loop1,loop2,vga),2];
           dest[where,3]:=pal2[getpixel(loop1,loop2,vga),3];
             { Create a new color and set it's from and to pallette values }
         END;
       END;
     END;
   cls (vga,0);
 END;

 {ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ}
 Procedure Crossfade (direction:boolean;del,farin:word);
   { This fades from one picture to the other in the direction specified
     with a del delay. It crossfades one degree for every value in farin.
     If farin=63, then a complete crossfade occurs }
 VAR loop1,loop2:integer;
     temp:pallette;
 BEGIN
   if direction then BEGIN
     temp:=source;
     for loop1:=0 to 255 do
       pal (loop1,source[loop1,1],source[loop1,2],source[loop1,3]);
     flip (vaddr2,vga);
     For loop1:=0 to farin do BEGIN
       waitretrace;
       for loop2:=0 to 255 do
         pal (loop2,temp[loop2,1],temp[loop2,2],temp[loop2,3]);
       for loop2:=0 to 255 do BEGIN
         if temp[loop2,1]dest[loop2,1] then dec (temp[loop2,1]);
         if temp[loop2,2]dest[loop2,2] then dec (temp[loop2,2]);
         if temp[loop2,3]dest[loop2,3] then dec (temp[loop2,3]);
           { Move temp (the current pallette) from source to dest }
       END;
       delay (del);
     END;
   END
   else BEGIN
     temp:=dest;
     for loop1:=0 to 255 do
       pal (loop1,dest[loop1,1],dest[loop1,2],dest[loop1,3]);
     flip (vaddr2,vga);
     For loop1:=0 to farin do BEGIN
       waitretrace;
       for loop2:=0 to 255 do
         pal (loop2,temp[loop2,1],temp[loop2,2],temp[loop2,3]);
       for loop2:=0 to 255 do BEGIN
         if temp[loop2,1]source[loop2,1] then dec (temp[loop2,1]);
         if temp[loop2,2]source[loop2,2] then dec (temp[loop2,2]);
         if temp[loop2,3]source[loop2,3] then dec (temp[loop2,3]);
           { Move temp (the current pallette) from dest to source }
       END;
       delay (del);
     END;
   END
 END;

 BEGIN
   clrscr;
   writeln ('Hello there! This trainer program is on cross fading. What will happen');
   writeln ('is this : The program will load in two .CEL files, FROM.CEL and TO.CEL');
   writeln ('into the virtual screen at vaddr and to the VGA screen. The pallettes');
   writeln ('of these two pictures are loaded into pal1 and pal2. Note that you');
   writeln ('could easily rewrite this to load in other types of files if you do');
   writeln ('not own Autodesk Animator to draw your files (The pictures presented');
   writeln ('here were drawn by Fubar, sqeezed by me ;)). A third screen is then');
   Writeln ('generated into vaddr2 (this takes 5-10 seconds on my 386-40). Note');
   writeln ('that you could dump vaddr2 to disk as a file instead of calculating it');
   writeln ('each time...it would be faster and be half the size of the two pictures.');
   Writeln ('The picture will then crossfade between the two. Hit a key and it will');
   writeln ('crossfade halfway and then exit.');
   writeln;
   writeln ('After one particular comment E-Mailed to me, I thought I should just add');
   writeln ('this : I am not an employee of Autodesk, and they do not pay me to promote');
   writeln ('their product. You have no idea how much I wish they would :)  I recieve');
   writeln ('absolutely _nothing_ for writing the trainer...');
   writeln;
   writeln;
   write ('Hit any key to continue ...');
   readkey;
   randomize;
   setupvirtual;
   setmcga;
   init;
   SetItUp;
   for loop1:=0 to 255 do
     pal (loop1,source[loop1,1],source[loop1,2],source[loop1,3]);
   flip (vaddr2,vga);
   delay (3000);

   dir:=TRUE;
   while keypressed do readkey;
   repeat
     crossfade(dir,20,63);
     dir:=not (dir);
     delay (1000);
   until keypressed;
   Readkey;
   crossfade(dir,20,20);
   readkey;
   settext;
   Writeln ('All done. This concludes the eleventh sample program in the ASPHYXIA');
   Writeln ('Training series. You may reach DENTHOR under the names of GRANT');
   Writeln ('SMITH/DENTHOR/ASPHYXIA on the ASPHYXIA BBS. I am also an avid');
   Writeln ('Connectix BBS user, and occasionally read RSAProg. E-mail me at :');
   Writeln ('    smith9@batis.bis.und.ac.za');
   Writeln ('The numbers are available in the main text. You may also write to me at:');
   Writeln ('             Grant Smith');
   Writeln ('             P.O. Box 270');
   Writeln ('             Kloof');
   Writeln ('             3640');
   Writeln ('             Natal');
   Writeln ('             South Africa');
   Writeln ('I hope to hear from you soon!');
   Writeln; Writeln;
   Write   ('Hit any key to exit ...');
   readkey;
   shutdown;
   FreeMem (VirScr2,64000);
 END.

 [BACK] Back

Discuss this article in the forums


Date this article was posted to GameDev.net: 7/16/1999
(Note that this date does not necessarily correspond to the date the article was written)

See Also:
Denthor's Asphyxia Tutorials

© 1999-2011 Gamedev.net. All rights reserved. Terms of Use Privacy Policy
Comments? Questions? Feedback? Click here!