Introduction | Example | Tutorial | Applications

Introduction - Peanut Butter Jelly Time MS Word Cursor

Change your coworker’s cursor to the Peanut Butter Jelly Time dancing banana with this MS Word VBA tutorial. The VBA code example stores byte strings in your Custom Document Properties so every time your colleagues open your Word document, the banana animated cursor will be restored and activated on their computers.

VBA Dancing Banana Prank

I don’t typically endorse this kind of tomfoolery, but I can’t resist. This is golden. When someone opens your Word document, this script changes their cursor to a dancing banana, a la “It’s Peanut Butter Jelly Time!” What more could you ask for? Don’t worry - when they exit the document, I was kind enough to change their cursor back to the default aero_arrow. Who says we can’t have a little harmless fun?

This also works with Excel. Keep reading to discover how.

Example - Peanut Butter Jelly Time MS Word Cursor

Change Cursor with VBA

Private Declare Function LoadCursorFromFile Lib "user32.dll" Alias "LoadCursorFromFileA" (ByVal lpFileName As String) As Long
Private Declare Function SetSystemCursor Lib "user32.dll" (ByVal hcur As Long, ByVal id As Long) As Long
'---------------------------------------------------------------------------------------------------
'---Script: ChangeCursor----------------------------------------------------------------------------
'---Posted by: Ryan Wells---------------------------------------------------------------------------
'---Date: 03/2015-----------------------------------------------------------------------------------
'---Description: This VBA script chunks a *.ani file and stores the byte strings to the ------------
'----------------Custom Document Properties. After the initial setup, each time the file -----------
'----------------is opened, the *.ani file is recreated on the user's machine and the --------------
'----------------cursor will change to the *.ico file specified in BananaLoc. ----------------------
'---------------------------------------------------------------------------------------------------
Private Enum Cursors
    OCR_APPSTARTING = 32650 'The application starting (arrow and hourglass) cursor.
    OCR_CROSS = 32515 'The cross-shaped cursor.
    OCR_IBEAM = 32513 'The text selection (I-beam) cursor.
    OCR_ICON = 32641 'Win NT only: The empty icon cursor.
    OCR_NO = 32648 'The "no"-symbol (circle with slash through it) cursor.
    OCR_NORMAL = 32512 'The normal arrow cursor.
    OCR_SIZE = 32640 'Win NT only: The four-arrow resize/move cursor.
    OCR_SIZEALL = 32646
    OCR_SIZENESW = 32643
    OCR_SIZENS = 32645
    OCR_SIZENWSE = 32642
    OCR_SIZEWE = 32644
    OCR_UP = 32516
    OCR_WAIT = 32514
End Enum
 
Sub ConvertBanana()
'Run this first. Change the string inside StoreBanana to the location of your ani file.
    Call StoreBanana("c:\temp\banana.ani")
End Sub

Private Sub StoreBanana(fn As String)
' Store byte strings in your custom document properties
    Dim Bytes As String, Bytestring As String
    
    ClearBanana
    
    Open fn For Binary Access Read As #1
        Bytes = Space(LOF(1))
        Get #1, , Bytes
    Close #1
   
    For i = 1 To Len(Bytes)
        Bytestring = Bytestring & Asc(Mid(Bytes, i, 1)) & " "
    Next
    Bytestring = Trim(Bytestring)
   
    Dim d As DocumentProperties
 
    Set d = ThisDocument.CustomDocumentProperties
   
    chunk = 0
    While chunk < Len(Bytestring)
        d.Add "RyanWellsCursor" & chunk / 255, False, MsoDocProperties.msoPropertyTypeString, Mid(Bytestring, chunk + 1, 255)
        chunk = chunk + 255
    Wend
 
    Set d = Nothing
 
End Sub
  
Sub AutoOpen()
    GetBanana
    ChangeCursor "c:\temp\banana.ani", False
End Sub
 
Sub AutoClose()
    ChangeCursor "C:\windows\cursors\aero_arrow.cur", False
End Sub
 
Private Sub ClearBanana()
    Dim d As DocumentProperty
   
    For Each d In ThisDocument.CustomDocumentProperties
        If d.Name Like "RyanWellsCursor*" Then
            ThisDocument.CustomDocumentProperties(d.Name).Delete
        End If
    Next
   
 
End Sub
 
Private Sub GetBanana()
    'Resurrects *.ani file from document properties and saves it as banana.ani
    Dim d As DocumentProperty, f As Integer, BananaLoc As String, Banana As String, Bytes
    BananaLoc = "c:\temp\banana.ani"
    f = FreeFile
   
    If Dir(BananaLoc) <> "" Then Kill BananaLoc
   
    For Each d In ThisDocument.CustomDocumentProperties
        If d.Name Like "RyanWellsCursor*" Then
            Banana = Banana & d.Value
        End If
    Next
   
    Bytes = Split(Banana, " ")
    Banana = ""
    For i = 0 To UBound(Bytes)
        Debug.Print i
        Banana = Banana & Chr(Int(Bytes(i)))
    Next
   
    Open BananaLoc For Binary Access Write As #f
        Put #f, , Banana
    Close #f
  
End Sub

Private Sub ChangeCursor(fn As String, alert As Boolean)
    'changes cursor
    Dim hCursor As Long
   
    Static PeanutButterJellyTime As Boolean
   
    hCursor = LoadCursorFromFile(fn)
   
    If hCursor Then
        Call SetSystemCursor(hCursor, Cursors.OCR_NORMAL)
       PeanutButterJellyTime = True
        If alert Then MsgBox "It's Peanut Butter Jelly Time!", vbOKOnly Or vbExclamation, "WHAT?!"
    End If
End Sub

Make powerful macros with our free VBA Developer Kit

It’s easy to copy and paste a macro like this, but it’s harder make one on your own. To help you make macros like this, we built a free VBA Developer Kit and wrote the Big Book of Excel VBA Macros full of hundreds of pre-built macros to help you master file I/O, arrays, strings and more - grab your free copy below.

I'll take a free VBA Developer Kit

Tutorial - Peanut Butter Jelly Time MS Word Cursor

Initial Setup
To get this to work on your victim's friend’s computer, you have to do some initial legwork.

  1. Download banana.ani and save it to C:\Temp.
  2. Open a Word document and save it as a .doc file. This allows you to avoid saving it as a macro-enabled document. We don’t want any dead giveaways, right?
  3. Paste ChangeCursor under Project (filename) > Microsoft Word Objects > ThisDocument in your VBA editor.
    1. Alt+F11 opens the VBA editor
      Project-Word-Objects-ThisDocument

  4. Execute the ConvertBanana macro.
    1. There are several ways to do this, one of which is to click Tools>Macros from your VBA editor. Run-ConvertBanana-Macro

  5. Save your file and close it.
    VBA Dancing Banana Prank

That’s it! The next time your coworker asks for a draft copy of that project you’ve been working on, embed this little trick in your document before sending it their way. Watch as their cursor magically changes to a dancing banana, regardless of what Windows computer they’re on. Before coming clean about your prank, be sure to capture the look of bewilderment on their face. That’s the best part.

Cursor Prank Explanation
Still reading? Let me explain how this works. When you executed the ConvertBanana macro, we read the *.ani file in binary format. We split the byte string into several strings and stored these strings in your document’s Custom Document Properties.

Word Custom Document Properties
Custom Document Properties

All those RyanWellsCursor properties are tiny pieces of the byte string that make up our original animated cursor file. Now, each time your word document is opened, AutoOpen calls GetBanana and reassemblies the byte strings. It recreates the banana.ani file in the user’s C:\Temp directory so it doesn’t matter what Windows computer they’re logged on to. It’s a clever application of file chunking.

Excel Cursor Prank
This also works with Microsoft Excel. Simply change ThisDocument to ThisWorkbook, follow the steps in the Initial Setup section and save as a macro-enabled workbook (.xlsm).

Application Ideas - Peanut Butter Jelly Time MS Word Cursor

You can have a lot of fun with this, but you can also use it to help you stand out in the crowd. For instance, if you have access to a .cur or .ani file generator, you can create custom cursors with your name. Set up your resume with the custom cursor to bait your recruiters into calling you. Talk about standing out and showing off your VBA skills!

(If you get a job using this approach, I’d sure appreciate a “thank you” donation!)

I’d love to hear stories of how your friends, family and coworkers reacted to this cursor swap. For more fun VBA tricks like this, subscribe using the form below.