MAKE,SURE,will,easy,someone,cool,tile,game,co
Quick Search for:  in language:    
MAKE,SURE,will,easy,someone,cool,tile,game,co
   Code/Articles » |  Newest/Best » |  Community » |  Jobs » |  Other » |  Goto » | 
CategoriesSearch Newest CodeCoding ContestCode of the DayAsk A ProJobsUpload
RentACoder Stats

 Code:  lines
 Jobs: 0 postings

 
Sponsored by:

 

You are in:

 
Login



Latest Code Ticker for RentACoder.
Wrapping Scrolling Text
By Paranoid_Androi d on 7/2


Create A Dummy File
By AML on 7/2


Click here to see a screenshot of this code!Captionbar manipulation!
By Peter Hebels on 7/2

(Screen Shot)

A Game Of War
By Co0nest on 7/2


Click here to see a screenshot of this code!KeyGen Example
By Bengie|NET on 7/2

(Screen Shot)

Click here to see a screenshot of this code!OpenBrowser v1.9
By Orlando Jerez on 7/2

(Screen Shot)

SendMessageBySt ring() Example
By Jaime Muscatelli on 7/2


Click here to see a screenshot of this code!FirstSunday
By Jan Paul Penning on 7/2

(Screen Shot)

Click here to see a screenshot of this code!Ikonz v1.0
By Gaurav Creations on 7/2

(Screen Shot)

Click here to put this ticker on your site!


Add this ticker to your desktop!


Daily Code Email
To join the 'Code of the Day' Mailing List click here!





Affiliate Sites



 
 
   

Tile Engine (tiler,res change,wav & midi player)

Print
Email
 
VB icon
Submitted on: 8/1/1999
By: Mike Miller  
Level: Not Given
User Rating: By 101 Users
Compatibility:

Users have accessed this code 8822 times.
 
 
     This will make it easy for someone to make a cool tile game. The coding on their part will take basicly nothing and produce a quality game. It also has a wav player, midi player and some other stuff. Check it out! The reason I made this is because every place i went to look for a tile engine, either didn't have one or the code was all in the form and was really jacked up. With the engine that I made(rattyrat13@aol.com) it is all in a moudle and very easy to understand. It currently supports up to 35 diferent tiles but that can be changed to make it more. MAKE SURE THAT AUTO-REDRAW IS ON! If autoredraw isn't true then you will have to make sure that all the picture boxes that are being used as the input are still visable to the user. 'Newly updated ---- I forgot to add about a transparent bitmap in here, so people who want just that, just steal that and take it. Also I want everybody to know that this engine is fast, because it uses BitBlit ( Bit Blit or Bitmap Blaster) not paintpicture. There is no reason that I can see to use direct-x for a tile engine, BitBlit is fast enough.
 

Windows API/Global Declarations:

Can't Copy and Paste this?
Click here for a copy-and-paste friendly version of this code!

    //**************************************
    //     
    //Windows API/Global Declarations for :T
    //     ile Engine (tiler,res change,wav & midi 
    //     player)
    //**************************************
    //     
    '''''''''''''''''''''''TM
    '''Funky Tile Engine'''
    '''Mike Miller '''
    '''1999'''
    '''''''''''''''''''''''
    'autoredraw must be true!
    'RattyRat13@aol.com
    Declare Function BitBlt Lib "gdi32" (ByVal hDestDC As Long, ByVal X As Long, ByVal Y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hSrcDC As Long, ByVal xSrc As Long, ByVal ySrc As Long, ByVal dwRop As Long) As Long
    Declare Function mciSendString Lib "winmm.dll" Alias "mciSendStringA" (ByVal lpstrCommand As String, ByVal lpstrReturnString As String, ByVal uReturnLength As Long, ByVal hwndCallback As Long) As Long
    Declare Function mciGetErrorString Lib "winmm.dll" Alias "mciGetErrorStringA" (ByVal dwError As Long, ByVal lpstrBuffer As String, ByVal uLength As Long) As Long
    Declare Function GetShortPathName Lib "kernel32" Alias "GetShortPathNameA" (ByVal lpszLongPath As String, ByVal lpszShortPath As String, ByVal cchBuffer As Long) As Long
    Declare Function sndPlaySound Lib "winmm" Alias "sndPlaySoundA" (ByVal lpSound As String, ByVal flag As Long) As Long
    Public Declare Function CreateBitmap Lib "gdi32" (ByVal nWidth As Long, ByVal nHeight As Long, ByVal nPlanes As Long, ByVal nBitCount As Long, lpBits As Any) As Long
    Public Declare Function SetBkColor Lib "gdi32" (ByVal hdc As Long, ByVal crColor As Long) As Long
    Public Declare Function SelectObject Lib "gdi32" (ByVal hdc As Long, ByVal hObject As Long) As Long
    Public Declare Function CreateCompatibleBitmap Lib "gdi32" (ByVal hdc As Long, ByVal nWidth As Long, ByVal nHeight As Long) As Long
    Public Declare Function CreateCompatibleDC Lib "gdi32" (ByVal hdc As Long) As Long
    Public Declare Function DeleteDC Lib "gdi32" (ByVal hdc As Long) As Long
    Public Declare Function DeleteObject Lib "gdi32" (ByVal hObject As Long) As Long
    Private Declare Function EnumDisplaySettings Lib "user32" Alias "EnumDisplaySettingsA" (ByVal lpszDeviceName As Long, ByVal iModeNum As Long, lpDevMode As Any) As Boolean
    Private Declare Function ChangeDisplaySettings Lib "user32" Alias "ChangeDisplaySettingsA" (lpDevMode As Any, ByVal dwflags As Long) As Long
    Const CCDEVICENAME = 32
    Const CCFORMNAME = 32
    Const DM_PELSWIDTH = &H80000;
    Const DM_PELSHEIGHT = &H100000;
    Public Type RECT
    Left As Long
    Top As Long
    Right As Long
    Bottom As Long
    End Type
    Private Type DEVMODE
    dmDeviceName As String * CCDEVICENAME
    dmSpecVersion As Integer
    dmDriverVersion As Integer
    dmSize As Integer
    dmDriverExtra As Integer
    dmFields As Long
    dmOrientation As Integer
    dmPaperSize As Integer
    dmPaperLength As Integer
    dmPaperWidth As Integer
    dmScale As Integer
    dmCopies As Integer
    dmDefaultSource As Integer
    dmPrintQuality As Integer
    dmColor As Integer
    dmDuplex As Integer
    dmYResolution As Integer
    dmTTOption As Integer
    dmCollate As Integer
    dmFormName As String * CCFORMNAME
    dmUnusedPadding As Integer
    dmBitsPerPel As Integer
    dmPelsWidth As Long
    dmPelsHeight As Long
    dmDisplayFlags As Long
    dmDisplayFrequency As Long
    End Type
    Dim DevM As DEVMODE
code:
Can't Copy and Paste this?
Click here for a copy-and-paste friendly version of this code!
 
Terms of Agreement:   
By using this code, you agree to the following terms...   
1) You may use this code in your own programs (and may compile it into a program and distribute it in compiled format for langauges that allow it) freely and with no charge.   
2) You MAY NOT redistribute this code (for example to a web site) without written permission from the original author. Failure to do so is a violation of copyright laws.   
3) You may link to this code from another website, but ONLY if it is not wrapped in a frame. 
4) You will abide by any additional copyright restrictions which the author may have placed in the code or code's description.

    //**************************************
    //     
    // Name: Tile Engine (tiler,res change,w
    //     av & midi player)
    // Description:This will make it easy fo
    //     r someone to make a cool tile game. The 
    //     coding on their part will take basicly n
    //     othing and produce a quality game. It al
    //     so has a wav player, midi player and som
    //     e other stuff. Check it out! The reason 
    //     I made this is because every place i wen
    //     t to look for a tile engine, either didn
    //     't have one or the code was all in the f
    //     orm and was really jacked up. With the e
    //     ngine that I made(rattyrat13@aol.com) it
    //     is all in a moudle and very easy to unde
    //     rstand. It currently supports up to 35 d
    //     iferent tiles but that can be changed to
    //     make it more. MAKE SURE THAT AUTO-REDRAW
    //     IS ON! If autoredraw isn't true then you
    //     will have to make sure that all the pict
    //     ure boxes that are being used as the inp
    //     ut are still visable to the user. 
    'Newly updated ---- I forgot to add about a transparent bitmap in here, so people who want just that, just steal that and take it. Also I want everybody to know that this engine is fast, because it uses BitBlit ( Bit Blit or Bitmap Blaster) not paintpicture. There is no reason that I can see to use direct-x for a tile engine, BitBlit is fast enough.
    // By: Mike Miller
    //
    // Inputs:The map file, if it isn't self
    //     explanitory, email me. And the PictureBo
    //     xes. Other than that there is some stuff
    //     if you want to use the non-engine part o
    //     f the moudle. The File Name For the WAV,
    //     Or MIDI, and the requried inputs for the
    //     transparent bliter.
    //
    // Returns:A BitBlited Form of a large p
    //     icture produced by many tiles, or even j
    //     ust 1 tile, it doesn't really matter.
    //
    // Assumes:TURN AUTOREDRAW ON!!!!!!
    If something is wrong, just try refreshing the form, in a timer with intraval of about 500 do
    me.refresh
    timer1.enabled = false
    end sub
    This will make everything better if it doesn't work.
    //
    // Side Effects:Beware of an extreamly c
    //     ool game made by you with this engine. N
    //     one Other than that though, if you find 
    //     one, e-mail it to me and I will correct 
    //     it and send you the corrected code along
    //     with everyone else who reads it, and you
    //     shall get some credit for helping me.
    //
    //This code is copyrighted and has    // limited warranties.Please see http://
    //     www.Planet-Source-Code.com/xq/ASP/txtCod
    //     eId.2747/lngWId.-10/qx/vb/scripts/ShowCo
    //     de.htm    //for details.    //**************************************
    //     
    
    Sub ChangeRes(iWidth As Single, iHeight As Single)
    'Just Call Changeres(1600,1200) or whatever you want in load
    Dim a As Boolean
    Dim i&
    i = 0
    Do
    a = EnumDisplaySettings(0&, i&, DevM)
    i = i + 1
    Loop Until (a = False)
    Dim b&
    DevM.dmFields = DM_PELSWIDTH Or DM_PELSHEIGHT
    DevM.dmPelsWidth = iWidth
    DevM.dmPelsHeight = iHeight
    b = ChangeDisplaySettings(DevM, 0)
    End Sub
    Public Sub TilePicture(frmDest As Form, source As PictureBox, X, Y)
    'This is not the sub that you want to use, it may be a good one to modify though
    'If you think you need Direct-X or just want to see what will work.
    Dim pw As Integer
    Dim ph As Integer
    Dim fw As Integer
    Dim fh As Integer
    Dim rst As Integer
    source.ScaleMode = 3
    pw = source.ScaleWidth
    ph = source.ScaleHeight
    fw = frmDest.Width / Screen.TwipsPerPixelX
    fh = frmDest.Height / Screen.TwipsPerPixelY
    iResult = BitBlt(frmDest.hdc, X, Y, iPicWidth, iPicHeight, picSource.hdc, 0, 0, vbSrcCopy)
    End Sub
    Public Sub LoadMap(InvisText As TextBox, mapname As String)
    'maps constists of numbers like
    '
    '00012301
    '12321455
    '51000102
    'and so forth, if anyone wants to make a map editor, that would be cool,
    'but I don't got the time(5:00 - 9:00pm) in football practice
    Dim lFileLength As Long
    Dim iFileNum As Integer
    iFileNum = FreeFile
    Open mapname For Input As iFileNum
    lFileLength = LOF(iFileNum)
    Text1.Text = Input(lFileLength, #iFileNum)
    Close iFileNum
    End Sub
    Public Sub OpenMidi()
    'dont call this, it needs a few mods
    Dim sFile As String
    Dim sShortFile As String * 67
    Dim lResult As Long
    Dim sError As String * 255
    sFile = App.Path & "\midtest.mid"
    lResult = GetShortPathName(sFile, sShortFile, Len(sShortFile))
    sFile = Left$(sShortFile, lResult)
    lResult = mciSendString("open " & sFile & _
    " type sequencer alias mcitest", ByVal 0&, 0, 0)
    If lResult Then
    lResult = mciGetErrorString(lResult, sError, 255)
    Debug.Print "open: " & sError
    End If
    End Sub
    Public Sub PlayMidi()
    'see above
    Dim lResult As Integer
    Dim sError As String * 255
    lResult = mciSendString("play mcitest", ByVal 0&, 0, 0)
    If lResult Then
    lResult = mciGetErrorString(lResult, sError, 255)
    Debug.Print "play: " & sError
    End If
    End Sub
    Public Sub CloseMidi()
    'again see above, i am sorry I will update soon
    Dim lResult As Integer
    Dim sError As String * 255
    lResult = mciSendString("close mcitest", "", 0&, 0&)
    If lResult Then
    lResult = mciGetErrorString(lResult, sError, 255)
    Debug.Print "stop: " & sError
    End If
    End Sub
    Sub PlayWave(sFileName As String)
    On Error GoTo Play_Err
    Dim iReturn As Integer
    If sFileName > "" Then
    If UCase$(Right$(sFileName, 3)) = "WAV" Then
    If Dir(sFileName) > "" Then
    iReturn = sndPlaySound(sFileName, 0)
    End If
    End If
    End If
    Exit Sub
    Play_Err:
    Exit Sub
    End Sub
    Function TileWalkable(Tilesize As Integer, LoadedMap As TextBox, X As Integer, Y As Integer, LineWidth As Integer) As Boolean
    'Funky Tile Engine Note:
    'Most pic boxes use twip, so divide pic.width by screen.twipsperpixelx and same for height, execpt for y insted.
    'I also suggest that you modify this if you are tring to make a more customized
    'engine, because this at this time gives you 18 unwalkables
    Dim xx As Integer
    Dim yy As Integer
    Dim temp As Integer
    Dim a As String
    Dim b As String
    xx = X / Tilesize
    yy = Y / Tilesize
    If Y < Tilesize Then
    a = Left(LoadedMap, xx)
    b = Mid(a, xx, 1): GoTo 1
    End If
    temp = yy * LineWidth + 2
    a = Left(LoadedMap, xx + temp)
    b = Mid(a, xx + temp, 1): GoTo 1
    1
    MsgBox b
    If b = "0" Then TileWalkable = False: Exit Function
    If b = "1" Then TileWalkable = False: Exit Function
    If b = "2" Then TileWalkable = False: Exit Function
    If b = "3" Then TileWalkable = False: Exit Function
    If b = "4" Then TileWalkable = False: Exit Function
    If b = "5" Then TileWalkable = False: Exit Function
    If b = "6" Then TileWalkable = False: Exit Function
    If b = "7" Then TileWalkable = False: Exit Function
    If b = "8" Then TileWalkable = False: Exit Function
    If b = "9" Then TileWalkable = False: Exit Function
    If b = "a" Then TileWalkable = False: Exit Function
    If b = "b" Then TileWalkable = False: Exit Function
    If b = "c" Then TileWalkable = False: Exit Function
    If b = "d" Then TileWalkable = False: Exit Function
    If b = "e" Then TileWalkable = False: Exit Function
    If b = "f" Then TileWalkable = False: Exit Function
    If b = "g" Then TileWalkable = False: Exit Function
    TileWalkable = True
    End Function
    Sub Tilemake(LoadedMap As TextBox, MapXLength As Integer, MapYLength, PicWidth As Integer, Dest As Form, Optional pic0 As PictureBox, Optional pic1 As PictureBox, Optional pic2 As PictureBox, Optional pic3 As PictureBox, Optional pic4 As PictureBox, Optional pic5 As PictureBox, Optional pic6 As PictureBox, Optional pic7 As PictureBox, Optional pic8 As PictureBox, Optional pic9 As PictureBox, Optional pic10 As PictureBox, Optional pic11 As PictureBox, Optional pic12 As PictureBox, Optional pic13 As PictureBox, Optional pic14 As PictureBox, Optional pic15 As PictureBox, Optional pic16 As PictureBox, Optional pic17 As PictureBox, Optional pic18 As PictureBox, Optional pic19 As PictureBox, Optional pic20 As PictureBox, Optional pic21 As PictureBox, Optional pic22 As PictureBox, Optional pic23 As PictureBox, Optional pic24 As PictureBox, Optional pic25 As PictureBox, Optional pic26 As PictureBox, Optional pic27 As PictureBox, Optional pic28 As PictureBox, Optional pic29 As PictureBox, _
    Optional pic30 As PictureBox, Optional pic31 As PictureBox, Optional pic32 As PictureBox, Optional pic33, Optional pic34 As PictureBox, Optional pic35 As PictureBox)
    'this is what you call
    'all pictureboxes are optional, so you don't have to use them all
    'Put me in the form paint
    'after 0123456789 comes a - z
    'be creative if you want more, ~!@#$%^&*()_+
    cc = 0
    aa = 0
    bb = 0
    1
    For i = 0 To MapXLength
    a = Mid(LoadedMap, i + aa + 1, 1)
    dd = i * PicWidth
    dd = dd + 224
    If a = "0" Then Call TilePicture(Dest, pic0, dd, cc)
    If a = "1" Then Call TilePicture(Dest, pic1, dd, cc)
    If a = "2" Then Call TilePicture(Dest, pic2, dd, cc)
    If a = "3" Then Call TilePicture(Dest, pic3, dd, cc)
    If a = "4" Then Call TilePicture(Dest, pic4, dd, cc)
    If a = "5" Then Call TilePicture(Dest, pic5, dd, cc)
    If a = "6" Then Call TilePicture(Dest, pic6, dd, cc)
    If a = "7" Then Call TilePicture(Dest, pic7, dd, cc)
    If a = "8" Then Call TilePicture(Dest, pic8, dd, cc)
    If a = "9" Then Call TilePicture(Dest, pic9, dd, cc)
    If a = "a" Then Call TilePicture(Dest, pic10, dd, cc)
    If a = "b" Then Call TilePicture(Dest, pic11, dd, cc)
    If a = "c" Then Call TilePicture(Dest, pic12, dd, cc)
    If a = "d" Then Call TilePicture(Dest, pic13, dd, cc)
    If a = "e" Then Call TilePicture(Dest, pic14, dd, cc)
    If a = "f" Then Call TilePicture(Dest, pic15, dd, cc)
    If a = "g" Then Call TilePicture(Dest, pic16, dd, cc)
    If a = "h" Then Call TilePicture(Dest, pic17, dd, cc)
    If a = "i" Then Call TilePicture(Dest, pic18, dd, cc)
    If a = "j" Then Call TilePicture(Dest, pic19, dd, cc)
    If a = "k" Then Call TilePicture(Dest, pic20, dd, cc)
    If a = "l" Then Call TilePicture(Dest, pic21, dd, cc)
    If a = "m" Then Call TilePicture(Dest, pic22, dd, cc)
    If a = "n" Then Call TilePicture(Dest, pic23, dd, cc)
    If a = "o" Then Call TilePicture(Dest, pic24, dd, cc)
    If a = "p" Then Call TilePicture(Dest, pic25, dd, cc)
    If a = "q" Then Call TilePicture(Dest, pic26, dd, cc)
    If a = "r" Then Call TilePicture(Dest, pic27, dd, cc)
    If a = "s" Then Call TilePicture(Dest, pic28, dd, cc)
    If a = "t" Then Call TilePicture(Dest, pic29, dd, cc)
    If a = "u" Then Call TilePicture(Dest, pic30, dd, cc)
    If a = "v" Then Call TilePicture(Dest, pic31, dd, cc)
    If a = "w" Then Call TilePicture(Dest, pic32, dd, cc)
    'If a = "x" Then Call TilePicture(Dest, pic33, dd, cc)
    'If a = "y" Then Call TilePicture(Dest, pic34, dd, cc)
    'If a = "z" Then Call TilePicture(Dest, pic35, dd, cc)
    Next i
    cc = cc + PicWidth
    aa = aa + MapXLength + 2
    bb = bb + 1
    If bb > MapYLength Then Exit Sub
    GoTo 1
    End Sub
    'Private Sub TransparentBlt(OutDstDC As Long, DstDC As Long, SrcDC As Long, SrcRect As RECT, DstX As Integer, DstY As Integer, TransColor As Long)
    ' Dim nRet As Long, W As Integer, H As Integer
    ' Dim MonoMaskDC As Long, hMonoMask As Long
    ' Dim MonoInvDC As Long, hMonoInv As Long
    ' Dim ResultDstDC As Long, hResultDst As Long
    ' Dim ResultSrcDC As Long, hResultSrc As Long
    ' Dim hPrevMask As Long, hPrevInv As Long
    ' Dim hPrevSrc As Long, hPrevDst As Long
    ' W = SrcRect.Right - SrcRect.Left + 1
    ' H = SrcRect.Bottom - SrcRect.Top + 1
    ' MonoMaskDC = CreateCompatibleDC(DstDC)
    ' MonoInvDC = CreateCompatibleDC(DstDC)
    ' hMonoMask = CreateBitmap(W, H, 1, 1, ByVal 0&)
    ' hMonoInv = CreateBitmap(W, H, 1, 1, ByVal 0&)
    ' hPrevMask = SelectObject(MonoMaskDC, hMonoMask)
    ' hPrevInv = SelectObject(MonoInvDC, hMonoInv)
    ' ResultDstDC = CreateCompatibleDC(DstDC)
    ' ResultSrcDC = CreateCompatibleDC(DstDC)
    ' hResultDst = CreateCompatibleBitmap(DstDC, W, H)
    ' hResultSrc = CreateCompatibleBitmap(DstDC, W, H)
    ' hPrevDst = SelectObject(ResultDstDC, hResultDst)
    ' hPrevSrc = SelectObject(ResultSrcDC, hResultSrc)
    ' Dim OldBC As Long
    ' OldBC = SetBkColor(SrcDC, TransColor)
    ' nRet = BitBlt(MonoMaskDC, 0, 0, W, H, SrcDC, SrcRect.Left, SrcRect.Top, vbSrcCopy)
    ' TransColor = SetBkColor(SrcDC, OldBC)
    ' nRet = BitBlt(MonoInvDC, 0, 0, W, H, MonoMaskDC, 0, 0, vbNotSrcCopy)
    ' nRet = BitBlt(ResultDstDC, 0, 0, W, H, DstDC, DstX, DstY, vbSrcCopy)
    ' nRet = BitBlt(ResultDstDC, 0, 0, W, H, MonoMaskDC, 0, 0, vbSrcAnd)
    ' nRet = BitBlt(ResultSrcDC, 0, 0, W, H, SrcDC, SrcRect.Left, SrcRect.Top, vbSrcCopy)
    ' nRet = BitBlt(ResultSrcDC, 0, 0, W, H, MonoInvDC, 0, 0, vbSrcAnd)
    ' nRet = BitBlt(ResultDstDC, 0, 0, W, H, ResultSrcDC, 0, 0, vbSrcInvert)
    ' nRet = BitBlt(OutDstDC, DstX, DstY, W, H, ResultDstDC, 0, 0, vbSrcCopy)
    ' hMonoMask = SelectObject(MonoMaskDC, hPrevMask)
    ' DeleteObject hMonoMask
    ' hMonoInv = SelectObject(MonoInvDC, hPrevInv)
    ' DeleteObject hMonoInv
    ' hResultDst = SelectObject(ResultDstDC, hPrevDst)
    ' DeleteObject hResultDst
    ' hResultSrc = SelectObject(ResultSrcDC, hPrevSrc)
    ' DeleteObject hResultSrc
    ' DeleteDC MonoMaskDC
    ' DeleteDC MonoInvDC
    ' DeleteDC ResultDstDC
    ' DeleteDC ResultSrcDC
    'End Sub
    'Dim R As RECT
    ' With R
    ' .Left = 0
    ' .Top = 0
    ' .Right = Picture1.ScaleWidth
    ' .Bottom = Picture1.ScaleHeight
    'End With
    '
    'TransparentBlt Form1.hDC, Form1.hDC, Picture1.hDC, R, 20, 20, vbblack


Other 3 submission(s) by this author

 

 
Report Bad Submission
Use this form to notify us if this entry should be deleted (i.e contains no code, is a virus, etc.).
Reason:
 
Your Vote!

What do you think of this code(in the Not Given category)?
(The code with your highest vote will win this month's coding contest!)
Excellent  Good  Average  Below Average  Poor See Voting Log
 
Other User Comments
8/1/1999 5:05:00 PM:Mike Miller(author)
It also has a transparent bitmap maker 
on the bottom in 'comments, so just 
take that away if you need to make a 
transparent blit for your sprite.
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/1/1999 5:18:00 PM:anti
This is definitly the best engine for 
vb I've ever seen.  Not only because of 
it's access, but because you can edit 
it to suit your needs.  I hope you win 
the code contest with this code!
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/2/1999 3:20:00 PM:Zymotic
Realllyy... Really AWSOME DUDE!
This 
kicks ass! You just got to win that 
contest! :)
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/2/1999 5:35:00 PM:Mayor Pirkle(I wish)
Not too shabby... By the way, I'm not 
that advanced yet, and where did those 
new types, "Form", and "PictureBox", 
etc come from? Or is that just a dumb 
question?
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/2/1999 8:27:00 PM:D.C.
This is an AWESOME code! I think you 
should win!
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/2/1999 9:34:00 PM:Mike Miller(Author)
That Pirkle, the types can be replaced 
with object, which is what most people 
use, but I think that using form and 
picturebox will be more productive by 
specifying what it is, so new users 
will know more about the code. Any 
question can be asked and I will awnser 
it. RattyRat13@aol.com if you haven't 
set up netscape mail or outlook. By the 
way, thanks for the complements 
everybody, as a 14 year old freshmem on 
the football team it feels prety good. 
I am going to update the code and put 
alot more comments and dim some stuff 
that I didn't dim before (if any) so 
they wont be declared as varible. I 
will soon tell everybody a link to 
download the code in action too. If 
anybody wants to put this code on their 
site, please do! Just 
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/2/1999 9:34:00 PM:Michael Miller(continue)
please don't remove the comments that 
say my name. E-mail me if you make a 
really cool game out of it. And if you 
can manage to sell it, please put my 
name as the origanal engine maker. I 
use Linux and belive stuff should be 
free so here it is, modify it, use it, 
and sell a program made with it. It is 
trademarked but don't let that bother 
anybody, to have a legal trade mark all 
you have to do is just put the TM on 
something and be able to prove you have 
been using it for a while. NO SELLING 
THE ENGINE IT SELF THOUGH, IT IS SPOSED 
TO BE FREE! IF ANYONE WANTS TO BURN 
THIS TO A CD AND SELL THE CD, THAT IS 
OK, (Thats how RedHat makes money) JUST 
AS LONG AS YOU ONLY CHARGE FOR YOUR 
WORK. (I am sure you could jack this 
price up pretty high, paying yourself a 
lot, but I don't care.) I would like an 
email if you do happen to sell anything 
from the engine, so I can see what 
needs improvment in my engine and 
improve it.
Thanks for reading this 
long boring letter,
Michael Miller 
II
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/3/1999 4:40:00 PM:VbPrgmmer
Very nice tile engine, the only one 
that I can see that Planet Source Code 
has and its free.
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/6/1999 11:18:00 AM:PikApIkA
Woah,really cool code. I will put it on 
my website if its ok with you really 
soon. I hope you win
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/12/1999 7:15:00 PM:Bob
Ne1 have this zipped up? :)
 email 
them to me at 
bobseverson@hotmail.com
:) thanks!
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/13/1999 5:02:00 PM:Steve
Send It Here Zipped up, I'm havin some 
trouble getting it together 
here.
Steve
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/13/1999 9:28:00 PM:mike miller
i will send it unzipped to my linux 
webpage, the address should be 
members.linuxstart.com/~tux/fte.bas
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/14/1999 7:41:00 AM:Wouter Steenbergen
Hi there, I didn't use this code yet, 
but I think the people saying you sould 
win the contest didn't really look at 
the code...
I've got one idea 
allready... you should for instance try 
to change
If b="0" Then TlWlkbl = Fls: 
xt fnc
If b="1" Then TlWlkbl = Fls: xt 
fnc
... etc
to
const cTileWalkables 
= "0123456789ABCDEFG"
TileWalkable = 
instr(cTileWalkables,b) 
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/14/1999 6:40:00 PM:Mike Miller
Like i said, i made this to be easy, 
doing if's is much easier for anybody 
to chamge it. And if it isn't, it still 
works. Amd amyways I already won.
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/18/1999 2:33:00 PM:Jim
:( im a new programmer and cant make 
sense of anything.. I dont understand 
anything of this.. if someone does send 
me simplified forms or contact me. 
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/18/1999 7:30:00 PM:Bob
I don't understand ANY of this code. 
Can you send me the project in a zip 
file through e-mail? You can also send 
it to me through ICQ, my # is 35756599. 
Thanks in advance.
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/19/1999 9:12:00 AM:David YaY
I am a bit rusty on using this engine.. 
can someone send me a
zipped up 
example so i can see how you use all 
the
functions correctly?
Thnks!   
YaY
p.s. 
I see alot of people are 
having troube it might
be easier to 
have a exampleon the internet :-)
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/19/1999 9:09:00 PM:Jazzman
Quick Comment, can I get it in a ZIP 
file? What exactly does it DO? E-mail 
me!
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/20/1999 3:21:00 PM:Barnabas
hello, excuse me but this is 
the 
first tile enginge that i have seen in 
vb
(well actually i have not seen it 
yet) i have had the problem
of not 
getting to work becuase i do not know 
what
" I " am sposed to do. what 
controls should i put on there what do 
i name them
etc etc. someone please 
email me telling me(yes i am a beginer 
so please do not make fun of me
                 Barnabas
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
9/30/1999 11:47:00 AM:Rikiti
could you send it to me?
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
12/22/1999 2:44:24 PM:Albert Nicholas
My browser didn't load all codes when I 
tried to look at it. Can someone send 
the program to me. And please do it for 
me becuse I'm currently developing a 
game and need this technique.
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
5/9/2000 10:57:25 PM:BigNasty
could you post a sample project or 
something, im lost with how to use this 
im still a beginner Thanks!
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/10/2000 1:45:25 PM:SlicerMan
I don't quite understand how to use the 
engine. Like what should be in the form 
load to get the engine started, how to 
load the map, and the tiles. Sorry, I'm 
new at this. Send me at 
SlicerMan@hotmail.com Please. Thanks!
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/11/2000 6:49:23 PM:Mike Miller
Anybody want to make a roleplaying game 
with me(the designer of the engine). 
Email me. Rattyrat13@aol.com
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
8/23/2000 4:03:31 AM:Ashlawn Kemling
I have Tile Layer (Map Editor) that I 
made about a year ago that saves to a 
format similar to the numbers, but this 
code will help me speed up the 
redrawing process of the map.  I also 
apdapted the editor to make an engine 
which was basically the editor, but 
with movement controls.
--Ashlawn 
Kemling
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
3/14/2001 1:16:35 PM:Russell Judge
A suggestion on Sub TileMake, to allow 
an unlimited number of pictureboxes--in 
the sub, define only one picturebox and 
define it as a variant.  When calling 
it, pass it an array of pictureboxes.  
You can use Lbound and Ubound to find 
the limits of the array.  You'll need 
to refine the call to the Sub a little 
more to handle the lack of a hardcoded 
limit, but making such a change will 
improve the versatility of your engine. 
 After all, a sophisticated game might 
easily make use of more than 35 tiles.
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
3/4/2002 12:28:59 AM:reml
How do you directly load an image into 
a hDC without any pictureboxes?
Keep the Planet clean! If this comment was disrespectful, please report it:
Reason:

 
Add Your Feedback!
Note:Not only will your feedback be posted, but an email will be sent to the code's author in your name.

NOTICE: The author of this code has been kind enough to share it with you.  If you have a criticism, please state it politely or it will be deleted.

For feedback not related to this particular code, please click here.
 
Name:
Comment:

 

Categories | Articles and Tutorials | Advanced Search | Recommended Reading | Upload | Newest Code | Code of the Month | Code of the Day | All Time Hall of Fame | Coding Contest | Search for a job | Post a Job | Ask a Pro Discussion Forum | Live Chat | Feedback | Customize | RentACoder Home | Site Home | Other Sites | About the Site | Feedback | Link to the Site | Awards | Advertising | Privacy

Copyright© 1997 by Exhedra Solutions, Inc. All Rights Reserved.  By using this site you agree to its Terms and Conditions.  Planet Source Code (tm) and the phrase "Dream It. Code It" (tm) are trademarks of Exhedra Solutions, Inc.