Thread Rating:
  • 0 Vote(s) - 0 Average
  • 1
  • 2
  • 3
  • 4
  • 5
My greeting to Anya!!!!!
#1
Code:
'/This is a product of too much Secret of mana 2
'/Tried to emulate the magic I saw while playing the game.
'/Actually, this is my way of greeting my daughter a
'/Happy 3rd Birthday. :*)
'/RelSoft(Richard Eric M. Lope BSN RN)
'/SetVideoSeg By Plasma357(Jon Petrosky)

DECLARE SUB AF.Print (Xpos%, Ypos%, Text$, col%)
DECLARE SUB SetVideoSeg (Segment%)

DEFINT A-Z

DIM CosLut(1024) AS INTEGER                 'Speed
DIM SinLut(1024) AS INTEGER


REDIM SHARED Vpage(32009)  AS INTEGER       'SetVideoSeg Buffer

Linsize = (100 + 4) / 2                     'Size of each vertical line
DIM Textures(Linsize, 180) AS INTEGER       '180 lines

CLS
SCREEN 13

'D'oh Scale the Palette
FOR I = 0 TO 255
  OUT &H3C8, I
  OUT &H3C9, I \ 4
  OUT &H3C9, I \ 1
  OUT &H3C9, I \ 4
NEXT I

REDIM Vpage(32009) AS INTEGER        'Clear offscreen buffer
Vpage(6) = 2560                      'Width 320*8
Vpage(7) = 200                       'Height
Layer = VARSEG(Vpage(0)) + 1         'Buffer Seg(Ask Plasma)
SetVideoSeg Layer                    'Set Draw to Buffer



FOR Y = 0 TO 99                         'Draw some textures...
FOR X = 0 TO 180
    PSET (X, Y), Y OR X
NEXT X
NEXT Y

'And some Greetz
AF.Print 20, 15, "Happy BirthDay!!!!", 200
AF.Print 20, 30, "Anya Therese B. Lope", 138
AF.Print 20, 45, "April 9, 2003", 18
AF.Print 20, 60, "3 years old :*)", 230
AF.Print 20, 75, "Love: Mom & Dad", 200



Occurence = 20                      'Frequency

Ys = -1                             'Riiight.....
FOR a = 0 TO 1024
    Ys = (Ys + 1) MOD 360                   'Move Downwards
    Yss! = Ys * 3.141593 / 180              'Convert to rad
    SinLut(a) = SIN(Yss! + a / Occurence) * 128         'FixPoint
    CosLut(a) = COS(Yss! + a / Occurence) * 128
NEXT a

FOR X = 0 TO 179                        'Put 'em on the array
    GET (X, 0)-(X, 99), Textures(0, X)
NEXT X


W = 180                 'Flag Width
Mag! = 0                'Magnitude of waves
MagXV! = .05            'Secret Var....

FlagX = 15              'Top-Left of flag
FlagY = 15
Fxv = 2                 'Movement
Fyv = 1



DO


    FlagX = FlagX + Fxv         'Move the flag
    IF FlagX > 110 THEN         'Check for bounds
        Fxv = -Fxv
    ELSEIF FlagX < 16 THEN
        Fxv = -Fxv
    END IF

    FlagY = FlagY + Fyv         'Ditto
    IF FlagY > 79 THEN
        Fyv = -Fyv
    ELSEIF FlagY < 16 THEN
        Fyv = -Fyv
    END IF

    IF Mag! < 13 THEN           'Add magnitude until threshold
        Mag! = Mag! + MagXV!
    END IF
    

    SetVideoSeg Layer                    'Set Draw to Buffer
    LINE (0, 0)-(319, 199), 0, BF        'Cls
    Ys = (Ys + 1) MOD 1024

    'Add sines
    FOR X = 0 TO W - 1
        YT = (SinLut((Ys + X) MOD 1024) / 128) * Mag!
        XT = X + (SinLut((Ys + X) MOD 1024) / 128) * Mag!
        'Unrem the line below to see the standard one
        'XT =  X
        XxT = XT + 15
        PUT (XxT + FlagX, YT + FlagY), Textures(0, X), PSET
        PUT (XxT + 1 + FlagX, YT + FlagY), Textures(0, X), PSET
    NEXT X

    SetVideoSeg &HA000                    'Set Draw to Video
    WAIT &H3DA, 8                         'Wait
    PUT (0, 0), Vpage(6), PSET            'Blit to screen

LOOP UNTIL INKEY$ <> ""

SUB AF.Print (Xpos%, Ypos%, Text$, col%)
'Prints the standard 8*8 CGA font
'Paramenters:
'Segment=the Layer to print to
'Xpos,Ypos=the coordinates of the text
'Text$=the string to print
'col= is the color to print(gradient)

X% = Xpos%
Y% = Ypos%
Spacing% = 8
  FOR I% = 0 TO LEN(Text$) - 1
    X% = X% + Spacing%
    Offset% = 8 * ASC(MID$(Text$, I% + 1, 1)) + 14
    FOR J% = 0 TO 7
      DEF SEG = &HFFA6
      Bit% = PEEK(Offset% + J%)
      IF Bit% AND 1 THEN PSET (X%, Y% + J%), col%
      IF Bit% AND 2 THEN PSET (X% - 1, Y% + J%), col%
      IF Bit% AND 4 THEN PSET (X% - 2, Y% + J%), col%
      IF Bit% AND 8 THEN PSET (X% - 3, Y% + J%), col%
      IF Bit% AND 16 THEN PSET (X% - 4, Y% + J%), col%
      IF Bit% AND 32 THEN PSET (X% - 5, Y% + J%), col%
      IF Bit% AND 64 THEN PSET (X% - 6, Y% + J%), col%
      IF Bit% AND 128 THEN PSET (X% - 7, Y% + J%), col%
    NEXT J%
  NEXT I%


END SUB

SUB DrawFlag

H = 100
W = 180
LINE (0, 0)-(W, H), 15, BF
LINE (0, 0)-(W, H), 1, B

LINE (W, 0)-(W - (W / 3), H / 2), 1
LINE -(W, H), 1
LINE (W - (W / 3), H / 2)-(0, H / 2), 1

PAINT (1, 1), 1
PAINT (1, H - 1), 5, 1

Xx = W - 15
Yy = H / 2

CIRCLE (Xx, Yy), 4, 14
PAINT (Xx, Yy), 14
FOR I = 0 TO 359 STEP 45
    a! = I * 3.141593 / 180
    LINE (Xx, Yy)-(Xx + COS(a!) * 10, Yy + SIN(a!) * 10), 14
NEXT I

AF.Print W - 10, 10, "*", 14
AF.Print W - 10, H - 16, "*", 14
AF.Print W - 50, (H / 2) - 3, "*", 14

END SUB

SUB SetVideoSeg (Segment) STATIC

DEF SEG

IF VideoAddrOff& = 0 THEN ' First time the sub is called

' We need to find the location of b$AddrC, which holds the graphics
' offset (b$OffC) and segment (b$SegC). Since b$AddrC is in the default
' segment, we can find it by setting it to a certain value, and then
' searching for that value.

SCREEN 13 ' Set b$SegC to A000 (00A0 in memory)
PSET (160, 100), 0 ' Set b$OffC to 7DA0 (not needed in the IDE)

FOR Offset& = 0 TO 32764 ' Search for b$AddrC, which is
IF PEEK(Offset&) = &HA0 THEN ' in the default segment and
IF PEEK(Offset& + 1) = &H7D THEN ' should have a value of
IF PEEK(Offset& + 2) = &H0 THEN ' A0 7D 00 A0.
IF PEEK(Offset& + 3) = &HA0 THEN
VideoAddrOff& = Offset& + 2 ' If we found it, record the
EXIT FOR ' offset of b$SegC and quit
END IF ' looking. (Oddly, changing
END IF ' the b$OffC doesn't seem to
END IF ' do anything, so this is why
END IF ' this sub only changes b$SegC)
NEXT

END IF

' Change b$SegC to the specified Segment

POKE VideoAddrOff&, Segment AND &HFF
POKE VideoAddrOff& + 1, (Segment AND &HFF00&) \ &H100




END SUB
y smiley is 24 bit.
[Image: anya2.jpg]

Genso's Junkyard:
http://rel.betterwebber.com/
Reply
#2
Congratulations. Greetings from this sewer called Chile to your little daughter. [Image: xyxthumbs.gif]








...now that I'm thinking about it: this instead of a nice present? Awwww Reeeeel... :roll:
img]http://usuarios.vtr.net/~disaster/sigs/annoyizer.php[/img]
Reply
#3
Thanks VTR boy...

*da disaster saving the sanzo from an impending disaster called....

ie. RelLib
LOL
y smiley is 24 bit.
[Image: anya2.jpg]

Genso's Junkyard:
http://rel.betterwebber.com/
Reply
#4
give your daughter a cookie from me and wish her a happy birthday :lol:
[Image: jocke.gif]
Website: http://jocke.phatcode.net
"Some men get the world, other men get ex hookers and a trip to Arizona."
Reply
#5
Yeah, from me too (but two cookies.... Wink)
B 4 EVER
Reply
#6
This should have been on my site until I found out I had no site. LOL

:rotfl:
y smiley is 24 bit.
[Image: anya2.jpg]

Genso's Junkyard:
http://rel.betterwebber.com/
Reply
#7
That's a cool prog... Do you mind it being on my site when it is up?
Reply
#8
Quote:That's a cool prog... Do you mind it being on my site when it is up?

No prob,

here's another one:

Code:
DEFINT A-Z

REM $DYNAMIC

DIM Vpage(32001) AS INTEGER             'The Screen
DIM TextPage(32001) AS INTEGER          'Texture
DIM Wpage1(32001) AS INTEGER            'Ripple
DIM Wpage2(32001) AS INTEGER            'Ripple


Vpage(0) = 2560
Vpage(1) = 200
Vseg = VARSEG(Vpage(0))
Voff = VARPTR(Vpage(2))

TextPage(0) = 2560
TextPage(1) = 200
TextSeg = VARSEG(TextPage(0))
TextOff = VARPTR(TextPage(2))

Wpage1(0) = 2560
Wpage1(1) = 200
Wseg1 = VARSEG(Wpage1(0))
Woff1 = VARPTR(Wpage1(2))

Wpage2(0) = 2560
Wpage2(1) = 200
Wseg2 = VARSEG(Wpage2(0))
Woff2 = VARPTR(Wpage2(2))


CLS
SCREEN 13


'our Nasty Texture

FOR X = 0 TO 319
    FOR Y = 0 TO 199
        PSET (X, Y), (X OR Y) AND 255
NEXT Y, X

GET (0, 0)-(319, 199), TextPage(0)          'Get texture

Frames& = 0
DO

  Frames& = Frames& + 1
  IF Frames& AND 3 THEN                     'Poke a pixel
      DEF SEG = Wseg1                       'To start a ripple
      POKE Woff1 + (63195 * RND), 255
  END IF

  SWAP Wseg1, Wseg2                         'Magic
  SWAP Woff1, Woff2

  Ptr = 320 + Woff1
  Ptr2 = 320 + Woff2

                                            'Do ripple
  FOR I& = 320 TO 63680
    DEF SEG = Wseg1
    C% = PEEK(Ptr + 1) + PEEK(Ptr - 1) + PEEK(Ptr + 320) + PEEK(Ptr - 320)
    DEF SEG = Wseg2
    C% = (C% \ 2) - PEEK(Ptr2)
    C% = ABS(C% - C% \ 256)
    POKE Ptr2, C%
   Ptr = Ptr + 1
   Ptr2 = Ptr2 + 1
  NEXT I&

  Ptr = Woff1
  PtrVpage = Voff


  FOR Y = 0 TO 198
  FOR X = 0 TO 319
    DEF SEG = Wseg1
     Xoff = PEEK(Ptr + 1) - PEEK(Ptr)                 'Shading
     Yoff = PEEK(Ptr + 320) - PEEK(Ptr)
    DEF SEG = TextSeg
     Xt = X + Yoff \ 4
     Yt = Y + Xoff \ 4
     C = PEEK((320 * Yt) + Xt)
    DEF SEG = Vseg                                 'Poke to screen
     POKE PtrVpage, C
     Ptr = Ptr + 1
     PtrVpage = PtrVpage + 1
  NEXT X
  NEXT Y


  PUT (0, 0), Vpage(0), PSET                        'Blite screen
LOOP UNTIL LEN(INKEY$)


CLS
SCREEN 0
WIDTH 80
END
y smiley is 24 bit.
[Image: anya2.jpg]

Genso's Junkyard:
http://rel.betterwebber.com/
Reply
#9
Dude, that ripple effect is so cool.... but why did you have to use so much RAM?
am an asshole. Get used to it.
Reply
#10
Hmmmmmmmm.... Maybe I should make a 'relsoft' category in my downloads section... These progs are pretty cool. One day I will learn assembler and write some kickass Matrix-bullets-slow-down-and-show-their-path-through-the-atmosphere-with-3d-rotation thing :wink:
Reply


Forum Jump:


Users browsing this thread: 1 Guest(s)