Discussion in "Project Help" started by    elie    Sep 27, 2007.
Thu Sep 27 2007, 01:28 pm
#1
i would like to ask some help..
please help me on my project..my project is automatically sending of SMS via Nokia 3310 .. how do i interface nokia 3310 to the serial port of my PC..

Ii dont know how to program it..
im noob in interfacing..
what programming language should i use? is Visual Basic possible to use?
how?
please help me..
thanks..
Thu Sep 27 2007, 02:57 pm
#2
as i already said.. you can make use of VB to send sms...
here is a sample VB code..

Nokia FBUS SMS and PDU Utility Code and Notes

Private Sub Form_Unload(Cancel As Integer)
If MSComm1.PortOpen = True Then MSComm1.PortOpen = False
' This code assumes that you have a Form called SMS
' with the following on it:
' 1 x Microsoft COM Control V6.0
'
' DISCLAIMER
' This code and the information in it has been provided at no charge, for
' non commercial use and the author disclaims all liability of any kind
' relating to any use made of it
End Sub

Private Sub PDUEncoder_Click()
PDU.Show
' For details on the Nokia FBUS format, jump on the web and check out
' sites such as GNOKIA. There are also other sites which talk about
' the electronics needed to interface a PC or microcontroller to
' a Nokia phone that has an FBUS interface
'
' This code assumes that you have a Form called SMS
' with the following on it:
' 1 x Command Button (which is set to run this code when it is clicked)
'
' DISCLAIMER
' This code and the information in it has been provided at no charge, for
' non commercial use and the author disclaims all liability of any kind
' relating to any use made of it
End Sub

Private Sub SendSMS_Click()
' declare variables
Dim msg As String
Dim RdStr As String
Dim SndStr As String
Dim i
Dim FL As Integer

' clear the send and receive text boxes
Sent_String.Text = "": Rcvd_String = ""
SMS.Refresh

' if the COM port is closed, then open it
If MSComm1.PortOpen = False Then MSComm1.PortOpen = True

' ask for the message and get the PDU version
msg = InputBox("Message")
msg_pdu = Text_To_PDU(msg)

' get the SMSC phone number
' and convert it to FBUS format
Input_Phone = InputBox("SMSC Phone Number", , "+61411990010")
GoSub Convert_Phone_Number
SMSC_Number = Phone_Number

' get the SMS destination phone number
' and convert it to FBUS format
Input_Phone = InputBox("SMS Destination Phone Number", , "0431867231")
test_flag = True
GoSub Convert_Phone_Number

' set frame parameters
Frame_ID = Right$("0" & (CStr(Hex(&H1E))), 2)
DestDev = Right$("0" & (CStr(Hex(&H0))), 2)
SrcDev = Right$("0" & (CStr(Hex(&HC))), 2)
MsgType = Right$("0" & (CStr(Hex(&H2))), 2)
SMS_Frame_Hdr = Right$("0" & (CStr(Hex(&H0))), 2) & Right$("0" & (CStr(Hex(&H1))), 2) & Right$("0" & (CStr(Hex(&H0))), 2) & Right$("0" & (CStr(Hex(&H1))), 2) & Right$("0" & (CStr(Hex(&H2))), 2) & Right$("0" & (CStr(Hex(&H0))), 2)
SMSC_Details = SMSC_Number
Msg_Length_For_Calc = (Len(msg_pdu) / 2)
Msg_Text_Length = Right$("0" & CStr(Hex(Len(msg))), 2)
TPDU = Right$("0" & (CStr(Hex(&H15))), 2) & Right$("0" & (CStr(Hex(&H0))), 2) & Right$("0" & (CStr(Hex(&H0))), 2) & Right$("0" & (CStr(Hex(&H0))), 2)
vp = Right$("0" & (CStr(Hex(&HA7))), 2) & Right$("0" & (CStr(Hex(&H0))), 2) & Right$("0" & (CStr(Hex(&H0))), 2) & Right$("0" & (CStr(Hex(&H0))), 2) & Right$("0" & (CStr(Hex(&H0))), 2) & Right$("0" & (CStr(Hex(&H0))), 2) & Right$("0" & (CStr(Hex(&H0))), 2)
Frames_To_Go = Right$("0" & (CStr(Hex(&H1))), 2)
Seq_No = Right$("0" & (CStr(Hex(&H43))), 2)
Frame = Frame_ID & DestDev & SrcDev & MsgType & "00" & SMS_Frame_Hdr & SMSC_Details & TPDU & Msg_Text_Length & Phone_Number & vp & msg_pdu & Frames_To_Go & Seq_No

' Set Frame Length values
FL = (Len(SMS_Frame_Hdr) / 2) + (Len(SMSC_Details) / 2) + (Len(TPDU) / 2) + (Len(Msg_Text_Length) / 2) + (Len(Phone_Number) / 2) + (Len(vp) / 2) + (Len(msg_pdu) / 2) + (Len(Frames_To_Go) / 2) + (Len(Seq_No) / 2)
Frame_Length = FL

' check whether pad byte is necessary and add one
' if it is
Pad_Byte = ""
If FL Mod 2 <> 0 Then
' Frame is an odd length so add Pad Byte
Pad_Byte = Right$("0" & (CStr(Hex(&H0))), 2)
End If

' create frame
Buf_Frame = Frame
Frame = Left$(Buf_Frame, 10) & Right$("0" & CStr(Hex(Frame_Length)), 2) & Mid$(Buf_Frame, 11, Len(Buf_Frame) - 10)
Frame = Frame & Pad_Byte

' calculate checksums and add them to the frame
' there are two checksums for FBUS. The first
' is an exclusive or (XOR) of the characters in every
' odd position in the frame and the second is an
' exclusive or (XOR) of the characters in every even
' position in the frame (eg if a frame was
' 1E 0C 00 7F 00 02 02 03, the odd checksum value would
' be: 1E XOR 00 XOR 00 XOR 02 which results in a value
' of 1C and the even checksum byte would be:
' 0C XOR 7F XOR 02 XOR 03 which results in a value of 72
' note all values shown above are in hex
process_chr = ""
first_odd = True
first_even = True
char_pos = 0
For i = 1 To Len(Frame)
process_chr = process_chr & Mid$(Frame, i, 1)
If Len(process_chr) = 2 Then
Process_Value = CSng("&H" & process_chr)
char_pos = char_pos + 1
If char_pos Mod 2 <> 0 Then
' odd position
If first_odd = True Then
Odd_ChkSum = Process_Value
first_odd = False
Else
Odd_ChkSum = Odd_ChkSum Xor Process_Value
End If
Else
' even position
If first_even = True Then
Even_ChkSum = Process_Value
first_even = False
Else
Even_ChkSum = Even_ChkSum Xor Process_Value
End If
End If
process_chr = ""
End If
Next i
Odd_ChkSum = Hex(Odd_ChkSum)
Even_ChkSum = Hex(Even_ChkSum)
Frame = Frame & Right("0" & (CStr(Hex(CStr("&H" & Odd_ChkSum)))), 2) & Right("0" & (CStr(Hex("&H" & CStr(Even_ChkSum)))), 2)

' create a display friendly version of the frame to be sent
' so that we can display it
For i = 1 To Len(Frame)
Out_Chr = Out_Chr & Mid$(Frame, i, 1)
If Len(Out_Chr) = 2 Then
Output_Frame = Output_Frame & Out_Chr & " "
Out_Chr = ""
End If
Next i

' create sms command to go to phone
process_chr = ""
Send_String = ""
For i = 1 To Len(Frame)
process_chr = process_chr & Mid$(Frame, i, 1)
If Len(process_chr) = 2 Then
Send_String = Send_String & Chr$(CSng("&H" & process_chr))
process_chr = ""
End If
Next i

' display what we are about to send
For i = 1 To 127: Sent_String.Text = Sent_String.Text & "55 ": Next i
Sent_String.Text = Sent_String.Text & "55" & Chr$(13) & Chr$(10)
Sent_String.Text = Sent_String.Text & Chr(13) & Chr(10) & Output_Frame

' refresh the form to ensure that the values are displayed
SMS.Refresh

' send 128 'U's' (0x55) (55D) to start an FBUS session
For i = 1 To 128
MSComm1.Output = Chr$(85)
Next i

' send the command
MSComm1.Output = Send_String

' display reply by looping and displaying any characters
' that are received from the phone.
' The First_Flag value is used in the formatting logic.
' It ensures that a new line for each response from the
' phone does not occur on the first response (this avoids
' a blank line in your Text Box)
First_Flag = True
CheckRX:
If MSComm1.InBufferCount <> 0 Then
RdStr = MSComm1.Input
For i = 1 To Len(RdStr) Step 2
If i <> 1 Then Rcvd_String.Text = Rcvd_String.Text & " "
If CStr(Hex(Asc(Mid$(RdStr, i, 2)))) = "1E" And First_Flag = False Then Rcvd_String.Text = Rcvd_String.Text & Chr(13) & Chr(10)
Rcvd_String.Text = Rcvd_String.Text & Right$("0" & CStr(Hex(Asc(Mid$(RdStr, i, 2)))), 2)
First_Flag = False
Next i
Rcvd_String.Refresh
End If
DoEvents
GoTo CheckRX

Exit Sub

Convert_Phone_Number:
If Left$(Input_Phone, 1) = "+" Then
Phone_Number = "91"
Input_Phone = Mid$(Input_Phone, 2, Len(Input_Phone) - 1)
Else
Phone_Number = "81"
End If
Process_Digit = ""
Pad_Digits = 10
For i = 1 To Len(Input_Phone)
Process_Digit = Process_Digit & Mid$(Input_Phone, i, 1)
If Len(Process_Digit) = 2 Then
Phone_Number = Phone_Number & Right$(Process_Digit, 1) & Left$(Process_Digit, 1)
Process_Digit = ""
Pad_Digits = Pad_Digits - 1
End If
Next i
If Len(Process_Digit) = 1 Then
' We have an orphaned digit caused by
' a phone number with an odd number of
' digits, so create Fn where n = the
' orphaned digit
Phone_Number = Phone_Number & "F" & Process_Digit
Pad_Digits = Pad_Digits - 1
End If
Buf_Phone_Number = Phone_Number
If test_flag = False Then
Phone_Number = Right$(("0" & CStr(11 - Pad_Digits)), 2) & Buf_Phone_Number
Else
Phone_Number = "0A" & Buf_Phone_Number
End If
For i = 1 To Pad_Digits
Phone_Number = Phone_Number & "00"
Next i
Return

' NOTES
'
' For details on the Nokia FBUS format, jump on the web and check out
' sites such as GNOKIA. There are also other sites which talk about
' the electronics needed to interface a PC or microcontroller to
' a Nokia phone that has an FBUS interface
'
' This code assumes that you have a Form called SMS
' with the following on it:
' 1 x Text Box called 'Sent_String' with Multi-Line set to True
' 1 x Text Box called 'Rcvd_String' with Multi-Line set to True
' 1 x Command Button (which is set to run this code when it is clicked)
' 1 x Microsoft COM Control V6.0

' DISCLAIMER
' This code and the information in it has been provided at no charge, for
' non commercial use and the author disclaims all liability of any kind
' relating to any use made of it
End Sub

Private Sub SMSFail_Click()
help_string = "If you can't get an SMS to work, here are some things to try" & Chr(13) & Chr(10) & Chr(13) & Chr(10)
help_string = help_string & _
"1. Press the Test / Reset Button to test the interface (and set a different FBUS sequence number)." & Chr(13) & Chr(10) & Chr(13) & Chr(10)
help_string = help_string & _
"2. Turn the phone on and off to reset it (and the FBUS sequence number)." & Chr(13) & Chr(10) & Chr(13) & Chr(10)
help_string = help_string & _
"3. If you get 4 responses from the phone when you use the Send SMS option, but you don't receive anything on the destination phone, make sure that:" & Chr(13) & Chr(10)
help_string = help_string & _
"a) the phone can send an SMS by sending one manually; and" & Chr(13) & Chr(10)
help_string = help_string & _
"b) you are entering the correct SMSC and destination phone numbers in the correct format. "
help_string = help_string & _
"SMSC phone numbers must be in international format (eg +61411990010). Destination numbers must be in international format (eg +61411990010) or their normal format (eg 0411990010) " & Chr(13) & Chr(10) & Chr(13) & Chr(10)
help_string = help_string & _
"4. If you do not get any responses from the phone when you use the Send SMS option, follow (1), then (2) above." & Chr(13) & Chr(10) & Chr(13) & Chr(10)
help_string = help_string & _
"5. Is your phone compatible with this Utility? It has only been tested with a Nokia 3310."

MsgBox "" & help_string

' NOTES
'
' For details on the Nokia FBUS format, jump on the web and check out
' sites such as GNOKIA. There are also other sites which talk about
' the electronics needed to interface a PC or microcontroller to
' a Nokia phone that has an FBUS interface
'
' This code assumes that you have a Form called SMS
' with the following on it:
' 1 x Command Button (which is set to run this code when it is clicked)
'
' DISCLAIMER
' This code and the information in it has been provided at no charge, for
' non commercial use and the author disclaims all liability of any kind
' relating to any use made of it
End Sub

Private Sub TestReset_Click()
' declare variables
Dim RdStr As String
Dim SndStr As String
Dim i As Single
Dim First_Flag As Boolean

Sent_String.Text = "": Rcvd_String = ""
SMS.Refresh

' if the COM port is closed, then open it
If MSComm1.PortOpen = False Then MSComm1.PortOpen = True

' display what we are about to send
For i = 1 To 127: Sent_String.Text = Sent_String.Text & "55 ": Next i
Sent_String.Text = Sent_String.Text & "55" & Chr$(13) & Chr$(10)
Sent_String.Text = Sent_String.Text & "1E 00 0C D1 00 07 00 01 00 03 00 01 60 00 72 D5" & Chr(13) & Chr(10)

' refresh the form to ensure that the values are displayed
SMS.Refresh

' create the command to send
SndStr = Chr$(30) & Chr$(0) & Chr$(12) & Chr$(209) & Chr$(0) & Chr(7) & Chr$(0) & Chr$(1) & Chr(0) & Chr(3) & Chr$(0) & Chr$(1) & Chr$(96) & Chr$(0) & Chr$(114) & Chr$(213)

' Send 128 'U's' (0x55) (55D) to start an FBUS session
For i = 1 To 128
MSComm1.Output = Chr$(85)
Next i

' send the command (in this case it is the command that gets the
' the phone to return its hardware and software details
MSComm1.Output = SndStr

' display reply by looping and displaying any characters
' that are received from the phone.
' The First_Flag value is used in the formatting logic.
' It ensures that a new line for each response from the
' phone does not occur on the first response (this avoids
' a blank line in your Text Box)
First_Flag = True
CheckRX:
If MSComm1.InBufferCount <> 0 Then
RdStr = MSComm1.Input
For i = 1 To Len(RdStr) Step 2
If i <> 1 Then Rcvd_String.Text = Rcvd_String.Text & " "
If CStr(Hex(Asc(Mid$(RdStr, i, 2)))) = "1E" And First_Flag = False Then Rcvd_String.Text = Rcvd_String.Text & Chr(13) & Chr(10)
Rcvd_String.Text = Rcvd_String.Text & Right$("0" & CStr(Hex(Asc(Mid$(RdStr, i, 2)))), 2)
First_Flag = False
Next i
Rcvd_String.Refresh
End If
DoEvents
GoTo CheckRX
'
' NOTES
'
' This code has two functions:
' 1. test whether your PC - Phone Interface is working
' 2. resets the phone message sequence number if you
' just sent an SMS.
'
' Function 2 is necessary as I have not implemented any
' sequence increment logic in this utility. This means that
' once you send an SMS, you can't send another one until
' you run this code (which sends a different sequence number
' to the phone, thereby allowing you to send another SMS. This
' sequence issue occurs as as the SMS send code uses the same
' sequence number and the phone will not accept the same
' sequence number twice in a row.
'
' This code starts an FBUS session (ie sends 128 'U's (hex 55's)) to
' the phone, then sends the command to return the hardware and
' software details of the phone.
'
' All data sent to and received from the phone must be hex characters
' and the sofwtare and hardware details that come back from the phone
' will be in PDU format.
'
' IMPORTANT NOTE: the command has only been tested on a Nokia 3310
' SECOND IMPORTANT NOTE: as there can be a delay between sending
' a command and getting a response, this code loops endlessly looking
' for responses from the phone (ie it does not time out). A Nokia 3310
' will send 4 responses to this command (one short one acknowledging
' the command and 3 identical (and longer) responses containing the
' hardware and software details). You can add timeout code if you want.
' If you don't then make sure that you put a Port close command somwhere
' else in your code

' For details on the Nokia FBUS format, jump on the web and check out
' sites such as GNOKIA. There are also other sites which talk about
' the electronics needed to interface a PC or microcontroller to
' a Nokia phone that has an FBUS interface
'
' This code assumes that you have a Form called SMS
' with the following on it:
' 1 x Text Box called 'Sent_String' with Multi-Line set to True
' 1 x Text Box called 'Rcvd_String' with Multi-Line set to True
' 1 x Command Button (which is set to run this code when it is clicked)
' 1 x Microsoft COM Control V6.0
'
' DISCLAIMER
' This code and the information in it has been provided at no charge, for
' non commercial use and the author disclaims all liability of any kind
' relating to any use made of it
End Sub

Private Sub Encode_Button_Click()
' declare variables
Dim encoded_text As String
Dim i As Integer

' clear any previous values
Encoded_Msg.Text = ""
ECLength.Text = ""
ECLength.Text = ""

' display length of unencoded message
UECLength.Text = Len(Unencoded_Msg.Text)

' refresh form
PDU.Refresh

' get encoded text
encoded_text = Text_To_PDU(Unencoded_Msg.Text)

' display encoded message
For i = 1 To Len(encoded_text) Step 2
If i <> 1 Then Encoded_Msg.Text = Encoded_Msg.Text & " "
Encoded_Msg.Text = Encoded_Msg.Text & Mid$(encoded_text, i, 2)
Next i

' display length of encoded message
ECLength.Text = Len(encoded_text) / 2

' refresh form
PDU.Refresh

' NOTES
'
' This code assumes that you have a Form called PDU
' with the following on it:
' 1 x Text Box called 'Unencoded_Msg' with Multi-Line set to True
' 1 x Text Box called 'UECLength'
' 1 x Text Box called 'Encoded_Msg' with Multi-Line set to True
' 1 x Text Box called 'ECLength'
' 1 x Command Button (which is set to run this code when it is clicked)
'
' DISCLAIMER
' This code and the information in it has been provided at no charge, for
' non commercial use and the author disclaims all liability of any kind
' relating to any use made of it
End Sub

Public Function Text_To_PDU(msg)
' declare variables
Dim bin_msg_chars(128) As String
Dim return_value As String
Dim borrow_value, i, n As Byte

' default return value to nothing
Text_To_PDU = ""

' return if there is no message to encode
If Len(msg) = 0 Then Exit Function

' put the binary value of each message character
' into the bin_msg_chars array
For i = 1 To Len(msg)
bin_msg_chars(i) = Dec_To_Bin(Asc(Mid$(msg, i, 1)))
Next i

' perform the encoding (see notes below)
borrow_value = 0: n = 0
For i = 1 To Len(msg)
If i <> Len(msg) Then
If bin_msg_chars(i) <> "!" Then
borrow_val = borrow_val + 1
If borrow_val = 8 Then borrow_val = 1
n = n + 1
return_string = return_string & Right$("0" & CStr(Hex(Bin_To_Dec(Right$(bin_msg_chars(i + 1), borrow_val) & bin_msg_chars(i)))), 2)
If borrow_val = 7 Then
bin_msg_chars(i + 1) = "!"
Else
bin_msg_chars(i + 1) = Mid$(bin_msg_chars(i + 1), 1, Len(bin_msg_chars(i + 1)) - borrow_val)
End If
End If
Else
n = n + 1
return_string = return_string & Right$("0" & CStr(Hex(Bin_To_Dec(bin_msg_chars(i)))), 2)
End If
Next i

' return the encoded mesage to the calling program
Text_To_PDU = return_string

' NOTES
'
' PDU ENCODING BASICS
'
' PDU encoding is performed by taking each 7 bit character and packing
' them into 8 bit characters. If you have more than 7 characters, this results
' in a compressed form of encoding as every 7th character is encoded into
' the previous 6 characters.
'
' Encoding can be done manually by taking the characters to be encoded, writing them
' down back to front (eg hello would be written 'olleh'), converting them to
' 7 bit binary and performing the process (working left to right) set out below. In essence
' this process involves making 8 bit characters from 7 bit characters by taking bits from
' successive characters.
'
' 1. For the first character (ie the 'h'), we need 1 bit to make it an 8 bit character.
' We get this by taking it from the last bit of the next character (ie the 'e') and adding
' it to the front of the character we are processing. For this example, the bit we would
' take would be a '1'(as 'e' is 110 0101 in binary). This gives us a first encoded character
' of 1110 1000 (as 'h' is binary 110 1000) so adding the '1' we took gives us 1110 1000.
' 2. As we have taken the last bit from the second character (ie the 'e'), we need to take
' 2 characters from the following character (ie the 'l') to make an 8 bit character.
' The two would be '00' (as 'l' is 110 1100 in binary). If we add these two bits to the
' character we are processing, we get 0011 0010 (as the 'e' was 110 0101, but became 110 010
' after we took the last bit to encode our first character).
' 3. This process continues for each character until we either:
' (a) reach a point where we have taken all of the bits from the next character (eg where we
' have taken 6 bits from a character (leaving 1 bit) and then have to process that character)
' and have another character in front of that to process. To do this, we would need to take
' all 7 bits of the following character. After we do this, there is nothing left of the following
' character so it is skipped (ie we don't process it). It is not lost as it has been encoded into
' the previous character; or
' (b) reach the last character (ie there are no more characters ahead of it). At this point we
' simply leave the last character as it is (ie we do nothing to it). For our 'hello' example, the
' last character will be 0x06 (ie 6 Hex or 0000 0110 binary)
' 4. Once you have completed this process, don't forget that you have worked from right to left, but the
' encoded values must be entered into your phone from left to right. For our example we would (working
' right to left) get 0x06 0xFD 0x9B 0x32 0xE8. However, the phone would need to see E8329BFD06
'
' If you want to check a manual encoding, the working should look like this:
'
' Chr o l l e h
' Hex 0x6F 0x6C 0x6C 0x65 0x68
' Bin 110 1111 110 1100 110 1100 110 0101 110 1000
'
' Bits 110 [1111] 110 1[100] 110 11[00] 110 010[1]
' taken
'
' Result 110 1111 1101 1001 1011 0011 0010 1110 1000
' 0x06 0xFD 0x9B 0x32 0xE8
'
' reverse the order to get the form that is used to send to your phone
' and you get the result: E8 32 FD 06 (all hex)
'
' THIS CODE
'
' As Visual Basic does not have a bit shift function, the code manipulates
' the message characters by turning them into binary values and pretty much
' applying the encoding method described above.
'
' While you could perform encoding with few less lines of code using something
' like c or c++ (which has bit shift functions), there is actually not a huge
' difference in code size and this method may make the code easier to understand
' as it follows the encoding method described above.
'
' DISCLAIMER
' This code and the information in it has been provided at no charge, for
' non commercial use and the author disclaims all liability of any kind
' relating to any use made of it
'
End Function

Public Function Dec_To_Bin(dec_val)
' declare variables
Dim leading_zero_flag As Boolean
Dim i, place_val As Byte
Dim pad_zeroes As String
' logic
leading_zero_flag = True
For i = 1 To 8
If i = 1 Then place_val = 128 Else place_val = place_val / 2
If dec_val / place_val >= 1 Then
Dec_To_Bin = Dec_To_Bin & "1"
dec_val = dec_val - place_val
leading_zero_flag = False
Else
If leading_zero_flag = False Then
Dec_To_Bin = Dec_To_Bin & "0"
End If
End If
Next i
pad_zeroes = ""
For i = 1 To 7 - Len(Dec_To_Bin)
pad_zeroes = pad_zeroes & "0"
Next i
Dec_To_Bin = pad_zeroes & Dec_To_Bin
'
' NOTES
' This code converts to binary by successively dividing
' the passed decimal value by 128, 64, 32, 16, 8, 4, 2 and 1
' and testing whether each result is greater than or equal to 1
' If it is greater than or equal to 1, then it sets the relevant
' bit value to a '1'. If it is not greater than or equal to 1, then
' it sets the relevant bit value to a '0' if the leading bit flag is set.
' This flag ensures that we get one leading zero for a 7 bit character
' that starts with a '0' (eg 011 0010) and no leading zeroes for a
' 7 bit character that starts with a '1' (eg 110 1000). This is critical
' for the bit manipulation logic in the 'Text_To_PDU' routine as it has
' to have 7 bit binary values
'
' DISCLAIMER
' This code and the information in it has been provided at no charge, for
' non commercial use and the author disclaims all liability of any kind
' relating to any use made of it
End Function

Public Function Bin_To_Dec(bin_val)
' declare variables
Dim i, place_val As Byte

' logic
bin_val = Right$("00000000" & bin_val, 8)
For i = 8 To 1 Step -1
If i = 8 Then place_val = 1 Else place_val = place_val * 2
If Mid$(bin_val, i, 1) = "1" Then
Bin_To_Dec = Bin_To_Dec + place_val
End If
Next i
'
' NOTES
' This code converts the passed binary value to decimal
' by successively adding 1, 2, 4, 8, 16, 32, 64 and 128
' depending on whether the relevant binary value bit is
' a '1' or a '0'.
' The padding of preceding zeroes at the start is needed
' as the 'Text_To_PDU' routine works with binary values
' of varying sizes. The padding ensures that this logic
' always gets an 8 bit binary value
'
' DISCLAIMER
' This code and the information in it has been provided at no charge, for
' non commercial use and the author disclaims all liability of any kind
' relating to any use made of it
End Function



[ Edited Thu Sep 27 2007, 02:57 pm ]
Tags Nokia 3310 FBUS using VBsend sms using VBsend sms from PCVB code for nokia 3310 FBUS
Thu Sep 27 2007, 04:28 pm
#3
what kind of data cable should I use to interface to the serial port of the PC?
Thu Sep 27 2007, 10:26 pm
#4
if you want to make use of datacable then you need to clear RTS and Set DTR signal in the program..
This can be done as shown below..
             MSComm1.Dtr = True
             MSComm1.Rts = False


you can directly connect your phone with datacable to the PC's com port.
Fri Sep 28 2007, 03:40 am
#5
what's the name of the datacable?

thank you Ajay..
Fri Sep 28 2007, 09:22 am
#6
Just ask for Nokia 3310 datacable.. thats all..
technically i think its called DAU9P or FBUS cable.. you need to check in your local market..
 senior like this.
Fri Sep 28 2007, 02:52 pm
#7
ah ok.. thanks a lot Ajay..
great help for me.. :-)
Thu Oct 04 2007, 01:08 pm
#8
hi ajay..
i have now datacable.. how do i start to make my project?
please help me.. i dont know what to do ..
I need ur help..
Thu Oct 04 2007, 06:24 pm
#9
just connect the datacable... with PC COM port... and take the above given code as reference and make your project.. If you face any problem. Ask me
Fri Oct 05 2007, 12:46 pm
#10
the code doesn't work .. i transferred it to visual basic.. and i tested it but it doesnt send a SMS.. nothing happened.. help me ajay please..
 nujra like this.

Get Social

Information

Powered by e107 Forum System

Downloads

Comments

Bobbyerilar
Thu Mar 28 2024, 08:08 am
pb58
Thu Mar 28 2024, 05:54 am
Clarazkafup
Thu Mar 28 2024, 02:24 am
Walterkic
Thu Mar 28 2024, 01:19 am
Davidusawn
Wed Mar 27 2024, 08:30 pm
Richardsop
Tue Mar 26 2024, 10:33 pm
Stevencog
Tue Mar 26 2024, 04:26 pm
Bernardwarge
Tue Mar 26 2024, 11:15 am