0% found this document useful (0 votes)
66 views

Code

This document contains code for a basic calculator application. It defines constants and declares functions for opening and querying the Windows registry. It also includes functions for performing arithmetic operations like addition, subtraction, multiplication and division. The main form code initializes variables, handles number key clicks and decimal points, and performs calculations when the equals key is pressed. It supports operations, clearing values, and setting the window to always be on top.

Uploaded by

tsohn_213
Copyright
© © All Rights Reserved
Available Formats
Download as DOC, PDF, TXT or read online on Scribd
0% found this document useful (0 votes)
66 views

Code

This document contains code for a basic calculator application. It defines constants and declares functions for opening and querying the Windows registry. It also includes functions for performing arithmetic operations like addition, subtraction, multiplication and division. The main form code initializes variables, handles number key clicks and decimal points, and performs calculations when the equals key is pressed. It supports operations, clearing values, and setting the window to always be on top.

Uploaded by

tsohn_213
Copyright
© © All Rights Reserved
Available Formats
Download as DOC, PDF, TXT or read online on Scribd
You are on page 1/ 24

About Form

Option Explicit
' Reg Key Security Options...
Const READ_CONTROL = &H20000
Const KEY_QUERY_VALUE = &H1
Const KEY_SET_VALUE = &H2
Const KEY_CREATE_SUB_KEY = &H4
Const KEY_ENUMERATE_SUB_KEYS = &H8
Const KEY_NOTIFY = &H10
Const KEY_CREATE_LINK = &H20
Const KEY_ALL_ACCESS = KEY_QUERY_VALUE + KEY_SET_VALUE + _
KEY_CREATE_SUB_KEY + KEY_ENUMERATE_SUB_KEYS + _
KEY_NOTIFY + KEY_CREATE_LINK + READ_CONTROL
' Reg Key ROOT Types...
Const HKEY_LOCAL_MACHINE = &H80000002
Const ERROR_SUCCESS = 0
Const REG_SZ = 1
' Unicode nul terminated string
Const REG_DWORD = 4
' 32-bit number
Const gREGKEYSYSINFOLOC = "SOFTWARE\Microsoft\Shared Tools Location"
Const gREGVALSYSINFOLOC = "MSINFO"
Const gREGKEYSYSINFO = "SOFTWARE\Microsoft\Shared Tools\MSINFO"
Const gREGVALSYSINFO = "PATH"
Private Declare Function RegOpenKeyEx Lib "advapi32" Alias "RegOpenKeyExA"
(ByVal hKey As Long, ByVal lpSubKey As String, ByVal ulOptions As Long, ByVal
samDesired As Long, ByRef phkResult As Long) As Long
Private Declare Function RegQueryValueEx Lib "advapi32" Alias "RegQueryValueExA"
(ByVal hKey As Long, ByVal lpValueName As String, ByVal lpReserved As Long,
ByRef lpType As Long, ByVal lpData As String, ByRef lpcbData As Long) As Long
Private Declare Function RegCloseKey Lib "advapi32" (ByVal hKey As Long) As Long
Private Sub cmdSysInfo_Click()
Call StartSysInfo
End Sub
Private Sub cmdOK_Click()
Unload Me
End Sub
Private Sub Form_Load()
Me.Caption = "About " & App.Title

lblVersion.Caption = "Version " & App.Major & "." & App.Minor & "." &
App.Revision
lblTitle.Caption = App.Title
End Sub
Public Sub StartSysInfo()
On Error GoTo SysInfoErr
Dim rc As Long
Dim SysInfoPath As String
' Try To Get System Info Program Path\Name From Registry...
If GetKeyValue(HKEY_LOCAL_MACHINE, gREGKEYSYSINFO,
gREGVALSYSINFO, SysInfoPath) Then
' Try To Get System Info Program Path Only From Registry...
ElseIf GetKeyValue(HKEY_LOCAL_MACHINE, gREGKEYSYSINFOLOC,
gREGVALSYSINFOLOC, SysInfoPath) Then
' Validate Existance Of Known 32 Bit File Version
If (Dir(SysInfoPath & "\MSINFO32.EXE") <> "") Then
SysInfoPath = SysInfoPath & "\MSINFO32.EXE"
' Error - File Can Not Be Found...
Else
GoTo SysInfoErr
End If
' Error - Registry Entry Can Not Be Found...
Else
GoTo SysInfoErr
End If
Call Shell(SysInfoPath, vbNormalFocus)
Exit Sub
SysInfoErr:
MsgBox "System Information Is Unavailable At This Time", vbOKOnly
End Sub
Public Function GetKeyValue(KeyRoot As Long, KeyName As String, SubKeyRef As
String, ByRef KeyVal As String) As Boolean
Dim i As Long
' Loop Counter
Dim rc As Long
' Return Code
Dim hKey As Long
' Handle To An Open Registry Key
Dim hDepth As Long
'
Dim KeyValType As Long
' Data Type Of A Registry Key
Dim tmpVal As String
' Tempory Storage For A Registry Key
Value

Dim KeyValSize As Long


' Size Of Registry Key Variable
'-----------------------------------------------------------' Open RegKey Under KeyRoot {HKEY_LOCAL_MACHINE...}
'-----------------------------------------------------------rc = RegOpenKeyEx(KeyRoot, KeyName, 0, KEY_ALL_ACCESS, hKey) ' Open
Registry Key
If (rc <> ERROR_SUCCESS) Then GoTo GetKeyError
tmpVal = String$(1024, 0)
KeyValSize = 1024

' Handle Error...

' Allocate Variable Space


' Mark Variable Size

'-----------------------------------------------------------' Retrieve Registry Key Value...


'-----------------------------------------------------------rc = RegQueryValueEx(hKey, SubKeyRef, 0, _
KeyValType, tmpVal, KeyValSize) ' Get/Create Key Value
If (rc <> ERROR_SUCCESS) Then GoTo GetKeyError

' Handle Errors

If (Asc(Mid(tmpVal, KeyValSize, 1)) = 0) Then


' Win95 Adds Null Terminated
String...
tmpVal = Left(tmpVal, KeyValSize - 1)
' Null Found, Extract From String
Else
' WinNT Does NOT Null Terminate String...
tmpVal = Left(tmpVal, KeyValSize)
' Null Not Found, Extract String
Only
End If
'-----------------------------------------------------------' Determine Key Value Type For Conversion...
'-----------------------------------------------------------Select Case KeyValType
' Search Data Types...
Case REG_SZ
' String Registry Key Data Type
KeyVal = tmpVal
' Copy String Value
Case REG_DWORD
' Double Word Registry Key Data Type
For i = Len(tmpVal) To 1 Step -1
' Convert Each Bit
KeyVal = KeyVal + Hex(Asc(Mid(tmpVal, i, 1))) ' Build Value Char. By Char.
Next
KeyVal = Format$("&h" + KeyVal)
' Convert Double Word To String
End Select
GetKeyValue = True
rc = RegCloseKey(hKey)
Exit Function
GetKeyError:
KeyVal = ""

' Return Success


' Close Registry Key
' Exit

' Cleanup After An Error Has Occured...


' Set Return Val To Empty String

GetKeyValue = False
rc = RegCloseKey(hKey)
End Function

' Return Failure


' Close Registry Key

Main Form
'-----------------------------------------------------------' Variable Declarations...
'-----------------------------------------------------------Option Explicit
Dim blnClr As Boolean
Dim bytOprtr As Byte
Dim dblOpnd1 As Double, dblOpnd2 As Double
Dim dblRslt As Double, dblMmry As Double
Dim intDecIndex As Integer
'************************************************************
' Win 32 API function for keeping window always on top
'************************************************************
Private Declare Function SetWindowPos Lib "user32" (ByVal hwnd As Long, ByVal
hWndInsertAfter As Long, ByVal x As Long, y, ByVal cx As Long, ByVal cy As Long,
ByVal wFlags As Long) As Long
Private Const HWND_TOPMOST = -1
Private Const HWND_NOTOPMOST = -2
Private Const SWP_NOMOVE = &H2
Private Const SWP_NOSIZE = &H1
Private Const TOPMOST_FLAGS = SWP_NOMOVE Or SWP_NOSIZE
Public Sub MakeNormal(hwnd As Long)
SetWindowPos hwnd, HWND_NOTOPMOST, 0, 0, 0, 0, TOPMOST_FLAGS
End Sub
Public Sub MakeTopMost(hwnd As Long)
SetWindowPos hwnd, HWND_TOPMOST, 0, 0, 0, 0, TOPMOST_FLAGS
End Sub
'-----------------------------------------------------------' Functions for arithmetic operations...
'-----------------------------------------------------------'Addition
Public Function funAdd(dblOpnd1 As Double, dblOpnd2 As Double) As Double
funAdd = dblOpnd1 + dblOpnd2

bytOprtr = 0
End Function
'Subtraction
Public Function funSub(dblOpnd1 As Double, dblOpnd2 As Double) As Double
funSub = dblOpnd1 - dblOpnd2
bytOprtr = 0
End Function
'Multiplication
Public Function funMult(dblOpnd1 As Double, dblOpnd2 As Double) As Double
funMult = dblOpnd1 * dblOpnd2
bytOprtr = 0
End Function
'Division
Public Function funDiv(dblOpnd1 As Double, dblOpnd2 As Double) As Double
If dblOpnd2 = 0 Then
MsgBox "Can not divide by zero!", vbOKOnly + vbCritical, "Error"
Exit Function
Else: funDiv = dblOpnd1 / dblOpnd2
End If
bytOprtr = 0
End Function
'Modulus
Public Function funMod(dblOpnd1 As Double, dblOpnd2 As Double) As Double
If dblOpnd2 = 0 Then
MsgBox "Can not divide by zero!", vbOKOnly + vbCritical, "Error!"
Else: funMod = dblOpnd1 Mod dblOpnd2
End If
bytOprtr = 0
End Function
'-----------------------------------------------------------' Procedure for printing numberkey on the display...
'-----------------------------------------------------------Public Sub cmd_Click(intIndex As Integer)
If txtdsply.Text = "0" Then
blnClr = "True"
End If
If blnClr = "True" Then
txtdsply.Text = CStr(intIndex)
ElseIf blnClr = "False" Then
If Len(txtdsply.Text) = 10 Then
MsgBox "Maximum of 10 digits!", vbOKOnly + vbCritical, "Error!"

Exit Sub
Else: txtdsply.Text = txtdsply.Text & CStr(intIndex)
End If
End If
blnClr = "False"
cmdresult.SetFocus
End Sub
'Procedure for the constant Pi
Public Sub cmdPi_Click()
txtdsply.Text = "3.1415926535897"
blnClr = "True"
cmdresult.SetFocus
End Sub

'-----------------------------------------------------------' Initializing values on from load...


'-----------------------------------------------------------Public Sub Form_Load()
txtdsply.Text = "0"
cmdMret.Enabled = False
cmdMclr.Enabled = False
cmdCopy.Enabled = False
mnuCopy.Enabled = False
mnuStd.Checked = True
mnuCmp.Checked = False
blnClr = "True"
End Sub
'-----------------------------------------------------------' Procedures for numberkey clicks...
'-----------------------------------------------------------'Procedure for the numberkeys control array
Public Sub Command1_Click(Index As Integer)
Call cmd_Click(Index)
End Sub
'Procedure for decimal point click
Public Sub cmdDec_Click()
'To make sure that there can be only one dec point in a number
intDecIndex = intDecIndex + 1
If intDecIndex = 1 Then
If blnClr = True Then

txtdsply.Text = "0" & "."


Else: txtdsply.Text = txtdsply.Text & "."
End If
blnClr = "False"
End If
cmdresult.SetFocus
End Sub
'Procedure for the "+/-" key
Public Sub cmdNeg_Click()
If Val(txtdsply.Text) > 0 Then
txtdsply.Text = "-" & txtdsply.Text
ElseIf Val(txtdsply.Text) < 0 Then
txtdsply.Text = Right(txtdsply.Text, (Len(txtdsply.Text) - 1))
End If
blnClr = "True"
cmdresult.SetFocus
End Sub
'-----------------------------------------------------------' Procedure for the "=" key...
'-----------------------------------------------------------Public Sub cmdresult_Click()
dblOpnd2 = Val(txtdsply.Text)
Select Case bytOprtr
Case 0
intDecIndex = 0
blnClr = "True"
Exit Sub
Case 1
dblRslt = funAdd(dblOpnd1, dblOpnd2)
Case 2
dblRslt = funSub(dblOpnd1, dblOpnd2)
Case 3
dblRslt = funMult(dblOpnd1, dblOpnd2)
Case 4
dblRslt = funDiv(dblOpnd1, dblOpnd2)
Case 5
dblRslt = funMod(dblOpnd1, dblOpnd2)
End Select
'When a positive number is coverted from a string, the first
'digit is a blank where the "-" sign would go in case of a
'negative number. This is to trim the blank space for positive numbers.
txtdsply.Text = IIf(dblRslt >= 0, Trim(CStr(dblRslt)), CStr(dblRslt))
intDecIndex = 0

blnClr = "True"
End Sub
'-----------------------------------------------------------' Procedures for the operation button clicks ...
'-----------------------------------------------------------'Addition
Public Sub cmdAdd_Click()
Call cmdresult_Click
dblOpnd1 = Val(txtdsply.Text)
bytOprtr = 1
intDecIndex = 0
blnClr = "True"
cmdresult.SetFocus
End Sub
'Subtraction
Public Sub cmdSub_Click()
Call cmdresult_Click
dblOpnd1 = Val(txtdsply.Text)
bytOprtr = 2
intDecIndex = 0
blnClr = "True"
cmdresult.SetFocus
End Sub
'Multiplication
Public Sub cmdMult_Click()
Call cmdresult_Click
dblOpnd1 = Val(txtdsply.Text)
bytOprtr = 3
intDecIndex = 0
blnClr = "True"
cmdresult.SetFocus
End Sub
'Division
Public Sub cmdDiv_Click()
Call cmdresult_Click
dblOpnd1 = Val(txtdsply.Text)
bytOprtr = 4
intDecIndex = 0
blnClr = "True"
cmdresult.SetFocus
End Sub

'Modulus
Public Sub cmdMod_Click()
dblOpnd1 = Val(txtdsply.Text)
bytOprtr = 5
intDecIndex = 0
blnClr = "True"
cmdresult.SetFocus
End Sub
'Reciprocal
Public Sub cmdRecp_Click()
If Val(txtdsply.Text) = 0 Then
MsgBox "Caon not divide by zero!", vbOKOnly + vbCritical, "Error!"
Exit Sub
Else: dblRslt = 1 / Val(txtdsply.Text)
End If
txtdsply.Text = CStr(dblRslt)
blnClr = "True"
intDecIndex = 0
cmdresult.SetFocus
End Sub
'Square root
Public Sub cmdSqrt_Click()
If Val(txtdsply.Text) < 0 Then
MsgBox "Invalid Operation!", vbOKOnly + vbCritical, "Error!"
Call cmdClr_Click
Exit Sub
End If
dblRslt = Sqr(Val(txtdsply.Text))
txtdsply.Text = CStr(dblRslt)
blnClr = "True"
intDecIndex = 0
cmdresult.SetFocus
End Sub
'-----------------------------------------------------------' Procedures for the memory commands...
'-----------------------------------------------------------'Memory Add
Public Sub cmdMadd_Click()
If txtdsply.Text <> "0" Then
dblMmry = dblMmry + Val(txtdsply.Text)
cmdMret.Enabled = True
cmdMclr.Enabled = True

End If
intDecIndex = 0
blnClr = "True"
cmdresult.SetFocus
End Sub
'Memory Clear
Public Sub cmdMclr_Click()
Dim strTemp As String
dblMmry = 0
cmdMret.Enabled = False
cmdMclr.Enabled = False
intDecIndex = 0
strTemp = Trim(Clipboard.GetText)
If strTemp = "" Then
cmdPaste.Enabled = False
mnuPaste.Enabled = False
Else: cmdPaste.Enabled = True
mnuPaste.Enabled = True
End If
blnClr = "True"
cmdresult.SetFocus
End Sub
'Memory Retrieve
Public Sub cmdMret_Click()
txtdsply.Text = CStr(dblMmry)
intDecIndex = 0
blnClr = "True"
cmdresult.SetFocus
End Sub
'Memory Save
Public Sub cmdMsav_Click()
If txtdsply.Text <> "0" Then
dblMmry = Val(txtdsply.Text)
cmdMret.Enabled = True
cmdMclr.Enabled = True
End If
intDecIndex = 0
blnClr = "True"
cmdresult.SetFocus
End Sub
'-----------------------------------------------------------' Clear Commands...

'-----------------------------------------------------------'Clear Entry
Public Sub cmdCerr_Click()
txtdsply.Text = "0"
intDecIndex = 0
cmdCopy.Enabled = False
blnClr = "True"
cmdresult.SetFocus
End Sub
'Clear All
Public Sub cmdClr_Click()
Dim strTemp As String
dblOpnd1 = 0
dblOpnd2 = 0
txtdsply.Text = "0"
intDecIndex = 0
cmdCopy.Enabled = False
mnuCopy.Enabled = False
'Enable the Paste buutton and menu item only if there is valid
'data in the clipboard
strTemp = Trim(Clipboard.GetText)
If strTemp = "" Then
cmdPaste.Enabled = False
mnuPaste.Enabled = False
Else: cmdPaste.Enabled = True
mnuPaste.Enabled = True
End If
blnClr = "True"
cmdresult.SetFocus
End Sub
'BackSpace
Public Sub cmdBckspc_Click()
txtdsply.Text = Left(txtdsply.Text, (Len(txtdsply.Text) - 1))
If txtdsply.Text = "" Then
txtdsply.Text = "0"
ElseIf Asc(Right(txtdsply.Text, 1)) = 46 Then
txtdsply.Text = Left(txtdsply.Text, Len(txtdsply.Text) - 1)
End If
cmdresult.SetFocus
End Sub
'------------------------------------------------------------

' Procedures for capturing and handling keystrokes...


'-----------------------------------------------------------'For numberkeys, arithmetic operators, "Esc", "Backspace" etc...
Public Sub Form_KeyPress(KeyAscii As Integer)
Select Case KeyAscii
'Cases 48 - 57 for numberkeys
Case 48
Call cmd_Click(0)
Case 49
Call cmd_Click(1)
Case 50
Call cmd_Click(2)
Case 51
Call cmd_Click(3)
Case 52
Call cmd_Click(4)
Case 53
Call cmd_Click(5)
Case 54
Call cmd_Click(6)
Case 55
Call cmd_Click(7)
Case 56
Call cmd_Click(8)
Case 57
Call cmd_Click(9)
'Decimal point
Case 46
Call cmdDec_Click
'Addition
Case 43
Call cmdAdd_Click
'Subtraction
Case 45
Call cmdSub_Click
'Multiplication
Case 42
Call cmdMult_Click
'Division
Case 47
Call cmdDiv_Click
' "=" key
Case 61
Call cmdresult_Click

' "Esc" key is used both for the Clr and Cerr buttons
Case 27
If txtdsply.Text = "0" Then
Call cmdClr_Click
Else
Call cmdCerr_Click
End If
'Backspace
Case 8
Call cmdBckspc_Click
Case 78
Call cmdNeg_Click
Case 110
Call cmdNeg_Click
End Select
End Sub
'To check for Ctrl+C and Ctrl+V
Public Sub Form_KeyDown(KeyAscii As Integer, Shift As Integer)
Dim intShift As Integer
intShift = Shift And 7 'Bitwise AND
If intShift = 2 Then
If KeyAscii = (67 Or 99) Then
Call cmdCopy_Click
ElseIf KeyAscii = (86 Or 118) Then
Call cmdPaste_Click
End If
End If
End Sub
'-----------------------------------------------------------' Miscellanious Procedures...
'-----------------------------------------------------------Public Sub txtdsply_Change()
If txtdsply.Text <> "0" Then
cmdCopy.Enabled = True
mnuCopy.Enabled = True
End If
End Sub
'Copy to clipboard
Public Sub cmdCopy_Click()
Clipboard.SetText (txtdsply.Text)
cmdresult.SetFocus
End Sub

Public Sub cmdPaste_Click()


Dim strTemp As String, intCtr As Integer, intIndex As Integer
strTemp = Trim(Clipboard.GetText()) 'Get clipboard text in a temp string
If IsNumeric(strTemp) = True Then
'This loop makes sure that only the
'first digit is a minus sign
For intCtr = 2 To Len(strTemp)
If Asc(Mid(strTemp, intCtr, 1)) = 45 Then
MsgBox "Invalid Number!", vbOKOnly + vbCritical, "Error!'"
Exit Sub
End If
Next
'This is to format the text
'in case the first or last digit is a dec points
If Asc(Left(strTemp, 1)) = 46 Then
strTemp = "0" & strTemp
ElseIf Asc(Right(strTemp, 1)) = 46 Then
strTemp = strTemp & "0"
End If
If Asc(Left(strTemp, 1)) = 45 Then
If Asc(Mid(strTemp, 2, 1)) = 46 Then
strTemp = "-" & "0" & Right(strTemp, (Len(strTemp) - 1))
End If
End If
'See if the text has a dec point
For intCtr = 1 To Len(strTemp)
If Asc(Mid(strTemp, intCtr, 1)) = 46 Then
intIndex = intIndex + 1
End If
Next
'This makes sure that the text is within the max size limit
If Len(strTemp) > 10 Then
If intIndex = 1 Then 'if the text has a dec point, round it of to 10 digits
txtdsply.Text = Left(Val(strTemp), 10)
Else: MsgBox "Maximum of 10 digits!", vbOKOnly + vbCritical, "Error!"
Exit Sub
End If
Else: txtdsply.Text = strTemp
End If
Else: MsgBox "Invalid Data!", vbOKOnly + vbCritical, "Error!"
End If
cmdresult.SetFocus
End Sub
Private Sub Form_Unload(Cancel As Integer)
End

End Sub
Private Sub Form_Activate()
mnuStd.Checked = True
mnuCmp.Checked = False
Call cmdClr_Click
End Sub
'-----------------------------------------------------------' Procedures for menu items...
'-----------------------------------------------------------Public Sub mnuExit_Click()
End
End Sub
Public Sub mnuCopy_Click()
Call cmdCopy_Click
End Sub
Public Sub mnuPaste_Click()
Call cmdPaste_Click
End Sub
Public Sub mnuAbout_Click()
frmAbout.Show vbModal
End Sub
Private Sub mnuStd_Click()
mnuStd.Checked = True
mnuCmp.Checked = False
Form1.Visible = True
Form2.Visible = False
End Sub
Private Sub mnuCmp_Click()
mnuStd.Checked = False
mnuCmp.Checked = True
If mnuAlways.Checked = True Then
MakeNormal Form1.hwnd
mnuAlways.Checked = False
End If
Form2.Visible = True
Form1.Visible = False
Form2.SetFocus
End Sub
Private Sub mnuAlways_Click()
If mnuAlways.Checked = False Then

mnuAlways.Checked = True
MakeTopMost Form1.hwnd
Else: mnuAlways.Checked = False
MakeNormal Form1.hwnd
End If
End Sub

Compact Form
Option Explicit
Dim blnClr As Boolean, bytOprtr As Byte
Dim intDecIndex As Integer
Dim dblOpnd1 As Double, dblOpnd2 As Double, dblRslt As Double
'************************************************************
' Win 32 API function for keeping window always on top
'************************************************************
Private Declare Function SetWindowPos Lib "user32" (ByVal hwnd As Long, ByVal
hWndInsertAfter As Long, ByVal x As Long, y, ByVal cx As Long, ByVal cy As Long,
ByVal wFlags As Long) As Long
Private Const HWND_TOPMOST = -1
Private Const HWND_NOTOPMOST = -2
Private Const SWP_NOMOVE = &H2
Private Const SWP_NOSIZE = &H1
Private Const TOPMOST_FLAGS = SWP_NOMOVE Or SWP_NOSIZE
Public Sub MakeNormal(hwnd As Long)
SetWindowPos hwnd, HWND_NOTOPMOST, 0, 0, 0, 0, TOPMOST_FLAGS
End Sub
Public Sub MakeTopMost(hwnd As Long)
SetWindowPos hwnd, HWND_TOPMOST, 0, 0, 0, 0, TOPMOST_FLAGS
End Sub
'-----------------------------------------------------------' Functions for arithmetic operations...
'-----------------------------------------------------------'Addition
Public Function funAdd(dblOpnd1 As Double, dblOpnd2 As Double) As Double
funAdd = dblOpnd1 + dblOpnd2
bytOprtr = 0
End Function
'Subtraction

Public Function funSub(dblOpnd1 As Double, dblOpnd2 As Double) As Double


funSub = dblOpnd1 - dblOpnd2
bytOprtr = 0
End Function
'Multiplication
Public Function funMult(dblOpnd1 As Double, dblOpnd2 As Double) As Double
funMult = dblOpnd1 * dblOpnd2
bytOprtr = 0
End Function
'Division
Public Function funDiv(dblOpnd1 As Double, dblOpnd2 As Double) As Double
If dblOpnd2 = 0 Then
MsgBox "Can not divide by zero!", vbOKOnly + vbCritical, "Error"
Exit Function
Else: funDiv = dblOpnd1 / dblOpnd2
End If
bytOprtr = 0
End Function
'-----------------------------------------------------------' Procedure for printing numberkey on the display...
'-----------------------------------------------------------Public Sub cmd_Click(intIndex As Integer)
If txtdsply.Text = "0" Then
blnClr = "True"
End If
If blnClr = "True" Then
txtdsply.Text = CStr(intIndex)
ElseIf blnClr = "False" Then
If Len(txtdsply.Text) = 10 Then
MsgBox "Maximum of 10 digits!", vbOKOnly + vbCritical, "Error!"
Exit Sub
Else: txtdsply.Text = txtdsply.Text & CStr(intIndex)
End If
End If
blnClr = "False"
End Sub
'Procedure for decimal point click
Public Sub cmdDec_Click()
'To make sure that there can be only one dec point in a number
intDecIndex = intDecIndex + 1
If intDecIndex = 1 Then
If blnClr = True Then
txtdsply.Text = "0" & "."

Else: txtdsply.Text = txtdsply.Text & "."


End If
blnClr = "False"
End If
End Sub
Private Sub cmdRslt_Click()
Call cmdresult_Click
End Sub
Private Sub cmdRstr_Click()
If mnuAlways.Checked = True Then
MakeNormal Form2.hwnd
mnuAlways.Checked = False
End If
Form1.Visible = True
Form2.Visible = False
End Sub
'-----------------------------------------------------------' Procedures for the operation button clicks ...
'-----------------------------------------------------------'Addition
Public Sub cmdAdd_Click()
Call cmdresult_Click
dblOpnd1 = Val(txtdsply.Text)
bytOprtr = 1
intDecIndex = 0
blnClr = "True"
End Sub
'Subtraction
Public Sub cmdSub_Click()
Call cmdresult_Click
dblOpnd1 = Val(txtdsply.Text)
bytOprtr = 2
intDecIndex = 0
blnClr = "True"
End Sub
'Multiplication
Public Sub cmdMult_Click()
Call cmdresult_Click
dblOpnd1 = Val(txtdsply.Text)
bytOprtr = 3

intDecIndex = 0
blnClr = "True"
End Sub
'Division
Public Sub cmdDiv_Click()
Call cmdresult_Click
dblOpnd1 = Val(txtdsply.Text)
bytOprtr = 4
intDecIndex = 0
blnClr = "True"
End Sub
'Procedure for the "+/-" key
Public Sub cmdNeg_Click()
If Val(txtdsply.Text) > 0 Then
txtdsply.Text = "-" & txtdsply.Text
ElseIf Val(txtdsply.Text) < 0 Then
txtdsply.Text = Right(txtdsply.Text, (Len(txtdsply.Text) - 1))
End If
blnClr = "True"
End Sub
'-----------------------------------------------------------' Procedure for the "=" key...
'-----------------------------------------------------------Public Sub cmdresult_Click()
dblOpnd2 = Val(txtdsply.Text)
Select Case bytOprtr
Case 0
intDecIndex = 0
blnClr = "True"
Exit Sub
Case 1
dblRslt = funAdd(dblOpnd1, dblOpnd2)
Case 2
dblRslt = funSub(dblOpnd1, dblOpnd2)
Case 3
dblRslt = funMult(dblOpnd1, dblOpnd2)
Case 4
dblRslt = funDiv(dblOpnd1, dblOpnd2)
End Select
'When a positive number is coverted from a string, the first
'digit is a blank where the "-" sign would go in case of a
'negative number. This is to trim the blank space for positive numbers.
txtdsply.Text = IIf(dblRslt >= 0, Trim(CStr(dblRslt)), CStr(dblRslt))

intDecIndex = 0
blnClr = "True"
End Sub
'-----------------------------------------------------------' Clear Commands...
'-----------------------------------------------------------'Clear Entry
Public Sub cmdCerr_Click()
txtdsply.Text = "0"
intDecIndex = 0
blnClr = "True"
cmdRslt.SetFocus
End Sub
'Clear All
Public Sub cmdClr_Click()
dblOpnd1 = 0
dblOpnd2 = 0
txtdsply.Text = "0"
intDecIndex = 0
blnClr = "True"
'cmdRslt.SetFocus
End Sub
'BackSpace
Public Sub cmdBckspc_Click()
txtdsply.Text = Left(txtdsply.Text, (Len(txtdsply.Text) - 1))
If txtdsply.Text = "" Then
txtdsply.Text = "0"
ElseIf Asc(Right(txtdsply.Text, 1)) = 46 Then
txtdsply.Text = Left(txtdsply.Text, Len(txtdsply.Text) - 1)
End If
End Sub
'-----------------------------------------------------------' Procedures for capturing and handling keystrokes...
'-----------------------------------------------------------'Copy to clipboard
Public Sub cmdCopy()
Clipboard.SetText (txtdsply.Text)
End Sub

Public Sub cmdPaste()


Dim strTemp As String, intCtr As Integer, intIndex As Integer
strTemp = Trim(Clipboard.GetText()) 'Get clipboard text in a temp string
If IsNumeric(strTemp) = True Then
'This loop makes sure that only the
'first digit is a minus sign
For intCtr = 2 To Len(strTemp)
If Asc(Mid(strTemp, intCtr, 1)) = 45 Then
MsgBox "Invalid Number!", vbOKOnly + vbCritical, "Error!'"
Exit Sub
End If
Next
'This is to format the text
'in case the first and last digits are dec points
If Asc(Left(strTemp, 1)) = 46 Then
strTemp = "0" & strTemp
ElseIf Asc(Right(strTemp, 1)) = 46 Then
strTemp = strTemp & "0"
End If
If Asc(Left(strTemp, 1)) = 45 Then
If Asc(Mid(strTemp, 2, 1)) = 46 Then
strTemp = "-" & "0" & Right(strTemp, (Len(strTemp) - 1))
End If
End If
'See if the text has a dec point
For intCtr = 1 To Len(strTemp)
If Asc(Mid(strTemp, intCtr, 1)) = 46 Then
intIndex = intIndex + 1
End If
Next
'This makes sure that the text is within the max size limit
If Len(strTemp) > 10 Then
If intIndex = 1 Then 'if the text has a dec point, round it of to 10 digits
txtdsply.Text = Left(Val(strTemp), 10)
Else: MsgBox "Maximum of 10 digits!", vbOKOnly + vbCritical, "Error!"
Exit Sub
End If
Else: txtdsply.Text = strTemp
End If
Else: MsgBox "Invalid Data!", vbOKOnly + vbCritical, "Error!"
End If
End Sub
Private Sub Form_Activate()
cmdRslt.SetFocus

End Sub
Public Sub Form_KeyDown(KeyCode As Integer, Shift As Integer)
Dim intShift As Integer
intShift = Shift And 7 'Bitwise AND
If intShift = 2 Then
Select Case KeyCode
Case 67
Call cmdCopy
Case 99
Call cmdCopy
Case 86
Call cmdPaste
Case 118
Call cmdPaste
Case 82
Call cmdRstr_Click
Case 114
Call cmdRstr_Click
End Select
End If
If intShift = 4 Then
Select Case KeyCode
Case 88
Call mnuExit_Click
Case 110
Call mnuExit_Click
End Select
End If
End Sub
Private Sub Form_KeyPress(KeyAscii As Integer)
Select Case KeyAscii
'Cases 48 - 57 for numberkeys
Case 48
Call cmd_Click(0)
Case 49
Call cmd_Click(1)
Case 50
Call cmd_Click(2)
Case 51
Call cmd_Click(3)
Case 52
Call cmd_Click(4)
Case 53
Call cmd_Click(5)

Case 54
Call cmd_Click(6)
Case 55
Call cmd_Click(7)
Case 56
Call cmd_Click(8)
Case 57
Call cmd_Click(9)
'Decimal point
Case 46
Call cmdDec_Click
'Addition
Case 43
Call cmdAdd_Click
'Subtraction
Case 45
Call cmdSub_Click
'Multiplication
Case 42
Call cmdMult_Click
'Division
Case 47
Call cmdDiv_Click
' "=" key
Case 61
Call cmdresult_Click
' "Esc" key is used both for the Clr and Cerr buttons
Case 27
If txtdsply.Text = "0" Then
Call cmdClr_Click
Else
Call cmdCerr_Click
End If
'Backspace
Case 8
Call cmdBckspc_Click
Case 78
Call cmdNeg_Click
Case 110
Call cmdNeg_Click
End Select
End Sub
Private Sub Form_Load()
Call cmdClr_Click

mnuAlways.Checked = True
MakeTopMost Form2.hwnd
End Sub
Private Sub Form_MouseUp(Button As Integer, Shift As Integer, x As Single, y As
Single)
If Button = 2 Then
Call Me.PopupMenu(mnuPopup)
End If
End Sub
Private Sub Form_Unload(Cancel As Integer)
End
End Sub
Private Sub mnuAlways_Click()
If mnuAlways.Checked = False Then
mnuAlways.Checked = True
MakeTopMost Form2.hwnd
Else: mnuAlways.Checked = False
MakeNormal Form2.hwnd
End If
End Sub
Private Sub mnuCopy_Click()
Clipboard.SetText (txtdsply.Text)
End Sub
Private Sub mnuExit_Click()
End
End Sub
Private Sub mnuPaste_Click()
Call cmdPaste
End Sub
Private Sub mnuRstr_Click()
Call cmdRstr_Click
End Sub

You might also like