Acustic Sensors

Embed Size (px)

Citation preview

  • 8/8/2019 Acustic Sensors

    1/31

    1

    POSITION DETECTION USINGULTRASONIC SENSORS

    INSTRUMENTATION&

    CONTROL

    INSTRUCTOR: OSMAN PARLAKTUNA

    26.01.2004

    MAHMUT SERKAN ZKANCELAL METEHAN AYDIN

    AL ZDEMR

  • 8/8/2019 Acustic Sensors

    2/31

    2

    INDEX

    I.PROJECT DESCRIPTION: 3

    II.PROCESS: 3

    III.HARDWARE: 5

    A.ULTRASONC SENSORS: 5B.MICROCONTROLLER,PIC 7C.MAX 232 8D.PC 8

    IV.SOFTWARE: 9

    A.FLOW CHART FORPIC: 10B.FLOW CHART FORPC: 11

    V.CONCLUSION: 13

    VI.APPENDIX A: URF SRF04 PIC 16F877 CODE 14

    VII. APPENDIX B: PROGRAM FOR PC 18

    VIII. APPENDIX C: REFERENCES 30

    IX.APPENDIX D: COST 31

  • 8/8/2019 Acustic Sensors

    3/31

    3

    I. PROJECT DESCRIPTION:

    Our project is position detection using ultrasonic sensors. Briefly; we try to measure the

    distance of an object from an ultrasonic sensor and map its position in a precalculated area. We use

    SRF04 ultrasonic sensors for distance measurement and drive this sensor via PIC (Peripheral Interface

    Control) 16f877 microcontroller. After getting the necessary data from sensor we make serial

    communication between PIC and PC and than mapping in PC using Visual Basic. We will first

    describe you the process than hardware that are used in our project and than talk about the software

    implementation and finally an evaluation about project.

    II.PROCESS:

    At the beginning of semester we try to decide which type of hardware to buy. Initially

    we want to use Polaroid 6500 ultrasonic module which exist in laboratory. Also one advantage of

    Polaroid is we make it work and search on how it works. After that we see that there will be lots of

    problems while using Polaroid. First one is its power problem. It requires 2A current which is very

    high for electronic applications. Also it has got serious connector problems between transducer-driver

    circuit and between control pins -power circuit. Than we search on and try to find another ultrasonic

    sensor module. After searching we find SRF04 which is economical in power consumption also

    smaller in size and easily controllable. We buy sensors via visa card from internet site www.robot-

    electronics.co.uk.

    Next stage for us is deciding on what kind of microcontroller we use. You can think of

    why we use microcontroller instead of directly connecting SRF04 to PC that contains A/D card. We

    use microcontroller because in timing measurements we need 66us sensitivity that can not be provided

    high-level languages. We initially think of Intel 8051 microprocessor. Again we search and find that

    PIC 16F877 microcontroller is much more suitable for our application.

    After we got sensors and our 16F877 we start on working. Initially we test sensors. We

    test how they work, and apply signals that are at different frequency. We find at what frequency we

    need to trigger sensors. Apart from this we test ECHO signal and find sensitivity approximately.

    Our test data is shown below:

  • 8/8/2019 Acustic Sensors

    4/31

    4

    In software part we try to develop algorithms for both triggering sensor via PIC and

    reading echo signal with PIC. After making PIC work we try to develop algorithm on PIC-PC serial

    communication. And lastly we develop codes for data processing on PC that converts time data to

    distance and map position on the screen. The diagram below shows us the general working principle of

    our system as schematic.

    In next stages we will describe the hardware and software parts in detailed.

    Test RangeMeasured

    Detection Distance

    Echo Output High

    Time

    1 7.5 cm 500 us

    2 15 cm 1000 us

    3 30 cm 2000 us

    4 60 cm 4000 us

    5 100 cm 6600 us

    PC SRF04PIC

    Serial communication,

    Read ECHO pulse width

    in time domain.

    Trigger

    Read ECHO pulse width

  • 8/8/2019 Acustic Sensors

    5/31

    5

    III. HARDWARE:

    We try to calculate the distance of an object using ultrasonic sensor, microcontroller and

    mapping with PC.

    A. Ultrasonic Sensors:

    The principle of working of an ultrasonic sensor is easy. The sensor transmits ultrasonic soundwaves and waits for reflected sound waves. After receiving reflected sound wave or usually named

    echo, sensor detects the distance in different ways. In our project we use SRF04 ultrasonic sensors.

    As seen in the figure it seems easy to use SRF04 ultrasonic sensor. Its main advantage is the

    number of pins that you have to use is only 4. One for Vdd, one for Vss, one for Trigger and one for

    Echo. Also one additional pin is given to adjust the range of the sensor. The other specifications of

    SRF04 ultrasonic sensors are

  • 8/8/2019 Acustic Sensors

    6/31

    6

    Voltage - 5v only required

    Current - 30mA Type. 50mA Max.

    Frequency - 40 KHz

    Max Range - 3 m

    Min Range - 3 cm

    Sensitivity - Detect 3cm diameter broom handle at > 2 m

    Input Trigger - 10uS Min. TTL level pulse

    Echo Pulse - Positive TTL level signal, width proportional to range.

    Small Size - 43mm x 20mm x 17mm height

    The important part for us is the signal conditioning of SRF04. We trigger the sensor and then

    wait for echo pulse. Measuring echo pulse width is important for us because 66.4 us means us 1 cm.

    As seen from timing diagram of SRF04 after triggering sensor with a TTL logic 1 (we use 5 V)

    at least 10 us, sonic burst module embedded in sensor makes 8 cycle sonic burst at 40 kHz. After the

    last sonic burst go low our echo signal became high and stay high until any reflected sound received

    by the sensor. Our initial objective is to trigger the sensor and than read the echo signal and measure

    its pulse width.

  • 8/8/2019 Acustic Sensors

    7/31

    7

    B. MICROCONTROLLER, PIC

    In this project we initially can not decide which microcontroller we will choose. We think of

    Intel 8051 or PIC. After researching on the net we decide to use PIC. PIC as its name implies

    (Peripheral Interface Controller) is designed by Microchip firm especially for Peripheral Interface

    jobs. Its main advantage is its memory structure. It has got Banks that shows each special register

    address (file registers). As PIC produced by RISC (Reduced Instruction Set) architecture we can see

    Harvard architecture that means the controller has got separate program memory which makes it faster

    than any other controller. One of the most important work is to chose the correct model that will

    support our project. For serial communication with PC we need Universal Synchronous Asynchronous

    Receiver Transmitter (USART/SCI) property. So we choose 16F877 which has got these properties.

    Our PIC has a 8K program memory which enables us write programs without thinking the

    capacity. Also we can use 14 external interrupts with this model. Additionally we have 5 ports (a, b, c,

    d, e), 3 timers, 2 counters and only 35 instructions to program.

    Our connection diagram is shown below:

    As shown we will use INIT1, INIT2, INIT3 to trigger the sensors and RC1 to read the ECHO1,

    ECHO2, and ECHO measuring the pulse width and make necessary operations we will send the data

  • 8/8/2019 Acustic Sensors

    8/31

    8

    through MAX232 with TX/CK Pin (25) .

    C. Max 232

    The MAX232 family of line drivers/receivers is intended for all EIA/TIA-232E and V.28/V.24

    communications interfaces, particularly applications where 12V is not available. This part is

    especially useful in battery-powered systems, since their low-power shutdown mode reduces power

    dissipation to less than 5W. The MAX232, use no external components and are recommended for

    applications where printed circuit board space is critical.

    Superior to Bipolar

    _ Operate from Single +5V Power Supply (+5V and +12VMAX232)

    _ Low-Power Receive Mode in Shutdown (MAX232/MAX242)

    _ Meet All EIA/TIA-232E and V.28 Specifications

    D. PC

    We used a PCs serial port to communicate between PIC and PC. The GUI (WYSIWYG) is :

  • 8/8/2019 Acustic Sensors

    9/31

    9

    IV. SOFTWARE:

  • 8/8/2019 Acustic Sensors

    10/31

    10

    A. Flow Chart for PIC:

    At the beginning of the program we initialize the PICs ports and registers, and USART

    configuration. Then PIC sends 150 ms trigger to the first SRF04 and listens the echo signal , after

    that SRF04 measures the distance and sends it to PIC. Furthermore PIC starts to measure the pulse

  • 8/8/2019 Acustic Sensors

    11/31

    11

    width of the received echo signal and transmits the pulse width to the PC. This routine repeated 2

    times more.

    B. Flow Chart for PC:

    At the loading, the program search for available ports and displays them on the Com Port

    frame. After that the user press the measure button, program starts a loop receives 16-bit serial data

    (Mscomm32.ocx supports 8-bit but we implement a code to overcome this problem) and starts to

    calculate. We observed calculated distance has a linear error so that we overcame this problem using

    curve fitting. In Matlab we entered the data and using curve fitting tool to obtain the transfer function

    which has minimum error. Furthermore using the Windows GUIs (gdi32) we display the measured

    object on the screen. Loop stops with the Stop button.

  • 8/8/2019 Acustic Sensors

    12/31

    12

  • 8/8/2019 Acustic Sensors

    13/31

    13

    V.CONCLUSION:

    During this project we learned that ;

    How bats measures the distance of an obstacle ?

    How sonar sensor works ?

    How Srf04 module works ?

    How can we interface the Srf04 with PIC 16f877 Microcontroller ?

    How to communicate between Srf04 and PC ?

    Finally we implement our system on breadboard and see on the PC the position of an obstacle.

    In fact, up to this point we suffer a lot. First problem we face is testing the sensors it takes much more

    time than we think. Also code development process for PIC is another problem for us. This problem is

    sourced by the necessity software development tools (PIC Programmer) that does not exist. At first we

    download our code to PIC than after it is a problem to make changes on code. So we made up a PIC

    16F877 programmer which is not working. Than we have to buy a programmer. Also we have got

    problems on serial communication because of the regulating necessary baud rate.

    In this project we gain lots of experience about project development process. Below you see

    our systems final schematic:

  • 8/8/2019 Acustic Sensors

    14/31

    14

    VI. APPENDIX A: URF SRF04 PIC 16F877 CODE

    ;************************************************************;; This is a program to run the PIC 16F877 to drive

    ; the SRF04. Port B will be used for the SRF04 module; drive, and the CCP1 pin for echo signals.; Below is the pin out

    ;; PORTB...; 0=INIT 1; 1=N/A

    ; 2=INIT 2; 3=N/A

    ; 4=INIT 3; 5=N/A; 6=N/A; 7=N/A

    ;; CCP1=ECHO 1 , ECHO 2 , ECHO3 respectively.

    ;;***********************************************************

    list P=PIC16F877, F=INHX8M, C=160, N=77, ST=OFF, MM=OFF, R=DEC, X=OFF#include P16F877.inc

    ; this is the standard header file for 16f877

    listlist__config(_CP_OFF & _PWRTE_ON & _XT_OSC & _WDT_OFF & _BODEN_OFF)

    ;********************** EQUATES ****************************

    Bank0Ram equ H'20'MaxCount equ 50;***********************************************************

    ;******************** VARIABLES ***************************

    cblock Bank0RamMACRO_TEMPTEMPTEMP2TIME1 ; this is the low byte for the Measured SignalTIME2 ; this is the high byte for the Measured Signal

    endc;***********************************************************

    ;****************** MACRO DEFINITIONS *******************MOVLF macro literal,dest

    movlw literalmovwf dest

    endm

    MOVFF macro source,destmovf source,Wmovwf destendm

    DELAY macro timelocal Again

  • 8/8/2019 Acustic Sensors

    15/31

    15

    movlw timemovwf MACRO_TEMP

    Againdecfsz MACRO_TEMPgoto Againendm

    ;********************************************************

    ;******************* VECTOR **************************

    org H'000' ;reset vectorsgoto MainLine ;Branch past tables

    ;*********************************************************

    ;******************* END OF TABLE *********************

    ;******************** MAIN ROUTINE **********************

    MainLinecall Initial ;initialize everything

    MainLoopcall FIRE_1 ;fire module 1MOVFF TMR1L,TIME1 ;save the low timeMOVFF TMR1H,TIME2 ;save the high timecall TRANSMIT ;transmit the data in Nibble1 - Nibble3

    call LoopTime ;wait for 10mscall FIRE_2 ;fire module 2MOVFF TMR1L,TIME1 ;save the low timeMOVFF TMR1H,TIME2 ;save the high timecall TRANSMIT ;transmit the data in TIME1 and TIME2call LoopTime ;wait for 10ms

    call FIRE_3 ;fire module 3MOVFF TMR1L,TIME1 ;save the low timeMOVFF TMR1H,TIME2 ;save the high timecall LoopTimecall TRANSMIT ;transmit the data in TIME1 and TIME2goto MainLoop

    ;***********************************************************

    ;*********************** INITIAL SUB ***********************;; this will initialize all of the ports and etc.

    Initial bsf STATUS,RP0 ;set to Bank 1MOVLF B'00000111',ADCON1 ;setting all AD pins to digital I/OMOVLF 160,TEMP2 ;setting LoopTime timeclrf TRISA ;setting all port a to outputclrf TRISB ;setting PORTB as out

    MOVLF B'00000100',TRISC ;all port c output, CCP1 inMOVLF B'11110000',TRISD ;all input for port dclrf TRISE ;all output for port emovlw 0x19 ; 0x0C=19200 baud (0x19=9600 baud)movwf SPBRGmovlw b'00100100' ; brgh = high (2)

    movwf TXSTA ; enable Async Transmission, set brgh

    movlw b'10010000' ; enable Async Reception bcf STATUS,RP0 ; RAM Page 0movwf RCSTA

  • 8/8/2019 Acustic Sensors

    16/31

    16

    clrf PORTAclrf PORTB

    clrf PORTCclrf PORTDclrf PORTEMOVLF B'10000000',RCSTA ;enable the serial port

    return;************************************************************

    ;****************** FIRE 1 SUBROUTINE **********************; This is used to set up and fire SRF04 1;********************* ------------------- *************************

    FIRE_1

    clrf TMR1H ;clear the timer 1 low byteclrf TMR1L ;clear the timer 1 low byteclrf PORTB ;ready PORTB bsf PORTB,0 ;set INIT 1call T20 ;delay for 20 us

    bcf PORTB,0 ;trigger low bcf PIR1,2 ;make sure CCP1 is clear

    ECHO1_LOOKING btfsc PORTC,2 ;testing CCP1goto ECHO1_LOOKING ; If not keep looking

    TIMERincf TMR1L ;Increment the Low byte

    btfsc STATUS, Z ;Do we have Zero (Multiple of 256)?incf TMR1H ;Increment High byte (if necessary) btfsc PORTC,2 ;testing CCP1goto TIMER ;make sure CCP1 is clearreturn

    ;************************************************************

    ;****************** FIRE 2 SUBROUTINE **********************; This is used to set up and fire SRF04 2;********************* ------------------- **************************

    FIRE_2clrf TMR1L ;clear the timer 1 low byteclrf PORTB ;ready PORTB bsf PORTB,2 ;set INIT 1call T20 ;delay for 20 us bcf PORTB,2 ;trigger low

    bcf PIR1,2 ;make sure CCP1 is clearECHO2_LOOKING

    btfsc PORTC,2 ;testing CCP1goto ECHO2_LOOKING

    TIMER2incf TMR1L ;Increment the Low byte

    btfsc STATUS, Z ;Do we have Zero (Multiple of 256)?incf TMR1H ;Increment High byte (if necessary) btfsc PORTC,2goto TIMER2return

    ;***********************************************************

    ;****************** FIRE 3 SUBROUTINE **********************; this is used to set up and fire SRF04 3

  • 8/8/2019 Acustic Sensors

    17/31

    17

    ;********************* ------------------- **************************

    FIRE_3clrf TMR1L ;clear the timer 1 low byteclrf PORTB ;ready PORTB bsf PORTB,4 ;set INIT 1

    call T20 ;delay for 20 us bcf PORTB,4 ;trigger low

    bcf PIR1,2 ;make sure CCP1 is clearECHO3_LOOKING

    btfsc PORTC,2 ;testing CCP1goto TIMER3goto ECHO3_LOOKING

    TIMER3

    incf TMR1L ;Increment the Low byte btfsc STATUS, Z ;Do we have Zero (Multiple of 256)?incf TMR1H ;Increment High byte (if necessary) btfsc PORTC,2goto TIMER3

    return;***********************************************************

    ;***************** TRANSMIT SUBROUTINE *********************;; This is used to send the data that is stored in

    ; TIME1 (low byte) and TIME2 (high byte) out the; serial port.;***********************************************************

    TRANSMITmovf TMR1H,0

    btfsc STATUS,2movlw b11111111movwf TXREGcall TransWt ; wait until finished sendingmovf TMR1L,0movwf TXREG

    call TransWtreturn

    ;**************** LoopTime SUBROUTINE **********************; This subroutine counts 10 mS;***********************************************************

    LoopTimedecfsz TEMP2,F

    call T20return

    ;***********************************************************

    ;************* *** T20 SUBROUTINE **************************; This will use up 10 us of time to ignore the; noise on the echo line from the fireing.;************************************************************

    T20

    MOVLF 20,TEMP ;a counter

    HEREdecfsz TEMP,F ;dec the countergoto HERE

  • 8/8/2019 Acustic Sensors

    18/31

    18

    return

    ;********** WAIT UNTIL RS232 IS FINISHED SENDING ***********

    TransWt bsf STATUS,RP0 ; RAM Page 1

    WtHere btfss TXSTA,TRMT ; (1) transmission is complete if higoto WtHere

    bcf STATUS,RP0 ; RAM Page 0return

    ;***********************************************************

    ;****************** END of ALL PROGRAMS ********************

    end

    VII. APPENDIX B: PROGRAM FOR PC

    FRMMAIN.frm

    Private Sub btnRead_Click()Dim bytInput() As ByteDim bytElemani As ByteDim iX As LongDim iY As LongDim iL As LongDim iP As LongDim SeriSonuc As String

    Dim sHistory As StringDim SeriVeri As StringDim Comment As StringIf comSerial.PortOpen = False ThencomSerial.PortOpen = TrueEnd If

    measure:Select Case comSerial.InBufferCountCase 0: MsgBox ("No data found")GoTo measureCase Is > 0:Say = comSerial.InBufferCountbytInput = comSerial.Input

    iX = UBound(bytInput(), 1)For iY = 0 To 1

    If SeriSonuc "" ThenIf iY Mod 4 Then

    SeriSonuc = "" & SeriSonucElse

    SeriSonuc = vbCrLf & SeriSonucEnd If

    End IfbytElemani = bytInput(iY)SeriVeri = Chr$(bytElemani)For iL = 1 To 8

    SeriSonuc = Abs(CInt(BitOn(CLng(bytElemani), iL))) & SeriSonuc

    NextNext'If BinaryToDecimal(SeriSonuc) * 6 > 4000 Then

  • 8/8/2019 Acustic Sensors

    19/31

    19

    'txtsrf042.Text = "Cisim Bulunamad"'Elsetxtrec1.Text = SeriSonuctxtmea1.Text = ((BinaryToDecimal(SeriSonuc) * 6) / (166 / 2.54)) & "

    cm"txtypos.Text = BinaryToDecimal(SeriSonuc) / 40 + 6

    'End IfIf txtmea1.DataChanged = True Then

    Comment = Now & " Received data ...: " & txtmea1.TextClose iFileNumSetLog (Comment)

    End IfGoTo measureEnd Select

    End Sub

    Private Sub btnview_Click()frmObjDist.Show

    End Sub

    Private Sub clrlog_Click()On Error GoTo ErrorTrpdel.DeleteFile ("data.txt")Exit SubErrorTrp:MsgBox ("History already cleared !!!")End Sub

    Private Sub Form_Initialize()BaudRate(0) = "110"BaudRate(1) = "300"BaudRate(2) = "600"BaudRate(3) = "1200"BaudRate(4) = "2400"BaudRate(5) = "9600"BaudRate(6) = "14400"BaudRate(7) = "19200"BaudRate(8) = "28800"BaudRate(9) = "38400"BaudRate(10) = "56000"BaudRate(11) = "128000"BaudRate(12) = "256000"

    End Sub

    Private Sub cmbBaudRate_Click()sBaudData = ""cmdUpdateBaud.Enabled = True

    End SubPrivate Sub cmbBaudRate_KeyPress(KeyAscii As Integer)

    Select Case KeyAsciiCase 48, 49, 50, 51, 52, 53, 54, 55, 56, 57

    sBaudData = sBaudData & Chr$(KeyAscii)Case 13

    sBaudData = ""UpdateBaud

    Case 127sBaudData = ""

    Case 8

    If sBaudData "" ThensBaudData = Left$(sBaudData, (Len(sBaudData) - 1))

    End If

  • 8/8/2019 Acustic Sensors

    20/31

    20

    Case ElsesBaudData = ""

    End SelectEnd SubPrivate Sub cmbBaudRate_Change()

    Dim iX As Long

    Dim iL As LongDim sCurrent As String

    If bLoaded ThencmdUpdateBaud.Enabled = TruesCurrent = sBaudDataiL = Len(sCurrent)

    For iX = 0 To 12If sCurrent = Left$(BaudRate(iX), iL) Then

    cmbBaudRate.Text = BaudRate(iX)cmbBaudRate.SelLength = Len(cmbBaudRate.Text)Exit Sub

    End If

    NextEnd IfEnd SubPrivate Sub cmdUpdateBaud_Click()

    UpdateBaudEnd Sub

    Function BitOn(Number As Long, Bit As Long) As BooleanDim iX As LongDim iY As Long

    iY = 1For iX = 1 To Bit - 1

    iY = iY * 2NextIf Number And iY Then BitOn = True Else BitOn = False

    End Function

    Private Sub VerifyPorts()Dim sPort As StringDim iX As LongDim iY As LongDim lngType As LongDim lngValue As LongDim sName As StringDim sSwap As StringReDim varResult(0 To 1, 0 To 100) As VariantConst lNameLen As Long = 260Const lDataLen As Long = 4096

    sSubKey = "Hardware\Devicemap\SerialComm"If RegOpenKeyEx(lMainKey, sSubKey, 0, KEY_READ, hnd) Then Exit Sub

    For iX = 0 To 999999If iX > UBound(varResult, 2) Then

    ReDim Preserve varResult(0 To 1, iX + 99)End IfsName = Space$(lNameLen)ReDim binValue(0 To lDataLen - 1) As ByteIf RegEnumValue(hnd, iX, sName, lNameLen, ByVal 0&, lngType,

    binValue(0), lDataLen) Then Exit For

    varResult(0, iX) = Left$(sName, lNameLen)

    Select Case lngType

  • 8/8/2019 Acustic Sensors

    21/31

    21

    Case REG_DWORDCopyMemory lngValue, binValue(0), 4varResult(1, iX) = lngValue

    Case REG_SZvarResult(1, iX) = Left$(StrConv(binValue(),

    vbUnicode), lDataLen - 1)

    Case ElseReDim Preserve binValue(0 To lDataLen - 1) As BytevarResult(1, iX) = binValue()

    End SelectNext

    If hnd Then RegCloseKey hndReDim Preserve varResult(0 To 1, iX - 1) As VariantReDim Ports(iX - 1)For iX = 0 To UBound(varResult, 2)

    sPort = Mid$(varResult(1, iX), 4, 1)Ports(iX) = sPort

    Next

    iY = UBound(Ports)For iX = 0 To (iY - 1)If Ports(iX + 1) < Ports(iX) Then

    sSwap = Ports(iX + 1)Ports(iX + 1) = Ports(iX)Ports(iX) = sSwapiX = -1

    End IfNext

    End SubPrivate Sub UpdateBaud()Attribute UpdateBaud.VB_Description = "Changes the baud rate of the serial port"

    Dim sNewBaud As StringDim sOldBaud As StringDim sTmp As StringDim iX As Long

    On Error GoTo ErrTrap

    sNewBaud = cmbBaudRate.TextFor iX = 0 To 12

    If BaudRate(iX) = sNewBaud ThenExit For

    ElseIf iX = 12 Then

    MsgBox "Invalid Baud Rate, Please Try Again !", vbInformation,"Data Entry Error !"

    sBaudData = ""cmbBaudRate.Text = ""cmdUpdateBaud.Enabled = FalseExit Sub

    End IfEnd If

    NextsTmp = comSerial.SettingssOldBaud = Left$(sTmp, (InStr(1, sTmp, ",", vbBinaryCompare) - 1))sTmp = Replace(sTmp, sOldBaud, sNewBaud, , , vbBinaryCompare)comSerial.Settings = sTmpcmdUpdateBaud.Enabled = False

    sBaudData = ""UpdateSettings

    Exit Sub

  • 8/8/2019 Acustic Sensors

    22/31

    22

    ErrTrap:

    MsgBox Err.Number & " " & Err.Description & vbCr & " Error Generated By "& Err.Source, vbCritical, _"System Error Trap !"End Sub

    Private Sub cmdExit_Click()Unload MeSet frmMain = Nothing

    End SubPrivate Sub cmdRead_Click()

    Dim bytInput() As ByteDim bytElement As ByteDim iX As LongDim iY As LongDim iL As LongDim iP As LongDim sResult As String

    Dim sHistory As StringDim sData As StringDim sSpace As String

    On Error GoTo ErrTrap

    If comSerial.PortOpen = False ThencomSerial.PortOpen = True

    End If

    bytInput = comSerial.InputiX = UBound(bytInput(), 1)For iY = 0 To iX

    If sResult "" ThenIf iY Mod 4 Then

    sResult = " " & sResultElse

    sResult = vbCrLf & sResultEnd If

    End IfbytElement = bytInput(iY)sData = Chr$(bytElement)For iL = 1 To 8

    Select Case iLCase 4

    sSpace = " , "Case Else

    sSpace = ""End SelectsResult = sSpace & Abs(CInt(BitOn(CLng(bytElement), iL))) &

    sResultNextIf sResult "" Then

    If Asc(sData) = 0 ThensData = "~"

    End IfsResult = "(" & sData & ")> " & sResult

    End IfNexttxtRead.Text = sResult & vbCrLf

    cmdRead.Enabled = FalselstHistory.AddItem ("Read " & sDataBits & " Bits" & " As " & sMode)Do While Len(sResult)

  • 8/8/2019 Acustic Sensors

    23/31

    23

    iP = InStrRev(sResult, "(", , vbBinaryCompare)sHistory = Replace(Trim(Mid$(sResult, iP)), vbCrLf, "", , ,

    vbBinaryCompare)sResult = Left(sResult, (iP - 1))lstHistory.AddItem (sHistory & " :ASCII " & CStr(Asc(Mid$(sHistory, 2,

    1))))

    LooptxtSend.SetFocustxtSend.SelStart = 0txtSend.SelLength = Len(txtSend.Text)cmdClearHistory.Enabled = True

    Exit Sub

    ErrTrap:MsgBox Err.Number & " " & Err.Description & vbCr & " Error Generated By "

    & Err.Source, vbCritical, _"System Error Trap !"End Sub

    Private Sub cmdSend_Click()On Error GoTo ErrTrap

    If comSerial.PortOpen = False ThencomSerial.PortOpen = True

    End IfcomSerial.Output = txtSend.TextcmdRead.Enabled = TruelstHistory.AddItem ("Send " & sDataBits & " Bits" & " As " & sMode)lstHistory.AddItem txtSend.TextExit Sub

    ErrTrap:MsgBox Err.Number & " " & Err.Description & vbCr & " Error Generated By "

    & Err.Source, vbCritical, _"System Error Trap !"End SubPrivate Sub Form_Load()

    Dim iX As LongDim iY As LongDim sTmp As StringDim sPort As StringDim sSelectedPort As StringDim bFlag As BooleanDim opt As OptionButton

    VerifyPortsVerifySettingssSettings = comSerial.SettingssSelectedPort = comSerial.CommPortSelect Case comSerial.InputMode

    Case comInputModeBinaryoptBinary.Value = TruesMode = "Binary"

    Case comInputModeTextoptString.Value = TruesMode = "String"

    End SelectFor iX = 0 To UBound(BaudRate())

    cmbBaudRate.AddItem BaudRate(iX)Next

    sTmp = Left$(sSettings, (InStr(1, sSettings, ",", vbBinaryCompare) - 1))sDataBits = Left$(Right$(sSettings, 3), 1)optDataBits(CInt(sDataBits)).Value = True

  • 8/8/2019 Acustic Sensors

    24/31

    24

    cmbBaudRate.Text = sTmp

    iY = UBound(Ports)For iX = 0 To iY

    sPort = Ports(iX)optPort(iX).Visible = True

    optPort(iX).Caption = sPortIf sPort = sSelectedPort ThenbFlag = TrueoptPort(iX).Value = True

    End IfNextIf Not bFlag Then

    comSerial.CommPort = CInt(optPort(0).Caption)optPort(0).Value = True

    End IfbLoaded = True

    End Sub

    Private Sub optBinary_Click()If bLoaded Then

    comSerial.InputMode = comInputModeBinarysMode = "Binary"

    End IfEnd SubPrivate Sub optDataBits_Click(Index As Integer)

    Dim sTmp As String

    On Error GoTo ErrTrap

    If bLoaded ThensTmp = comSerial.SettingsMid(sTmp, (Len(sTmp) - 2), 1) = CStr(Index)sDataBits = CStr(Index)comSerial.Settings = sTmpUpdateSettings

    End IfExit Sub

    ErrTrap:MsgBox Err.Number & " " & Err.Description & vbCr & " Error Generated By "

    & Err.Source, vbCritical, _"System Error Trap !"End SubPrivate Sub optPort_Click(Index As Integer)

    If bLoaded ThencomSerial.CommPort = CInt(optPort(Index).Caption)UpdateSettings

    End IfEnd SubPrivate Sub optString_Click()

    If bLoaded ThencomSerial.InputMode = comInputModeTextsMode = "String"

    End IfEnd Sub

    Private Sub txtSend_Change()

  • 8/8/2019 Acustic Sensors

    25/31

    25

    If txtSend.Text "" ThencmdSend.Enabled = True

    ElsecmdSend.Enabled = False

    End IfEnd Sub

    Private Sub cmdClearHistory_Click()lstHistory.ClearcmdClearHistory.Enabled = False

    End SubPrivate Sub txtSend_GotFocus()

    txtSend.SelStart = 0txtSend.SelLength = Len(txtSend.Text)

    End SubPrivate Sub VerifySettings()Attribute VerifySettings.VB_Description = "Checks the registry for the last comport settings"

    Dim disposition As LongDim sTmp As String

    On Error GoTo ErrTrap

    sSettings = comSerial.SettingssPortNum = comSerial.CommPortsSubKey = "Software\Damage Inc\Com Settings"If RegOpenKeyEx(lMainKey, sSubKey, 0, KEY_READ, hnd) Then

    If RegCreateKeyEx(lMainKey, sSubKey, 0, 0, 0, 0, 0, hnd, disposition)Then

    Err.Raise 1001, "VerifySettings() Sub", "Could Not Create RegistryKey"

    End IfEnd If

    sKeyValue = Space$(lLength)If RegQueryValueEx(hnd, sSettingsKey, 0, REG_SZ, ByVal sKeyValue, lLength)

    ThenIf RegOpenKeyEx(lMainKey, sSubKey, 0, KEY_WRITE, hnd) Then

    Err.Raise 1001, "VerifySettings() Sub", "Could Not Open RegistryKey"

    ElseIf RegSetValueEx(hnd, sSettingsKey, 0, REG_SZ, ByVal sSettings,

    Len(sSettings)) ThenErr.Raise 1001, "VerifySettings() Sub", "Could Not Set

    Registry Key Settings Value"End If

    End IfElse

    comSerial.Settings = sKeyValueEnd If

    sKeyValue = Space$(lLength)If RegQueryValueEx(hnd, sPortKey, 0, REG_SZ, ByVal sKeyValue, lLength)

    ThenIf RegOpenKeyEx(lMainKey, sSubKey, 0, KEY_WRITE, hnd) Then

    Err.Raise 1001, "VerifySettings() Sub", "Could Not Open Registry

    Key"Else

  • 8/8/2019 Acustic Sensors

    26/31

    26

    If RegSetValueEx(hnd, sPortKey, 0, REG_SZ, ByVal sPortNum,Len(sPortNum)) Then

    Err.Raise 1001, "VerifySettings() Sub", "Could Not SetRegistry Key Port Value"

    End IfEnd If

    ElsecomSerial.CommPort = sKeyValueEnd If

    RegCloseKey hndExit Sub

    ErrTrap:MsgBox Err.Number & " " & Err.Description & vbCr & " Error Generated By "

    & Err.Source, vbCritical, _"System Error Trap !"End Sub

    Private Sub UpdateSettings()Attribute UpdateSettings.VB_Description = "Updates the registry entry to thecurrent com port settings"

    On Error GoTo ErrTrap

    sSettings = comSerial.SettingssPortNum = comSerial.CommPortsSubKey = "Software\Damage Inc\Com Settings"

    If RegOpenKeyEx(lMainKey, sSubKey, 0, KEY_WRITE, hnd) ThenErr.Raise 1001, "VerifySettings() Sub", "Could Not Open Registry

    Key"Else

    If RegSetValueEx(hnd, sSettingsKey, 0, REG_SZ, ByVal sSettings,Len(sSettings)) Then

    Err.Raise 1001, "VerifySettings() Sub", "Could Not SetRegistry Key Settings Value"

    End IfEnd If

    If RegOpenKeyEx(lMainKey, sSubKey, 0, KEY_WRITE, hnd) ThenErr.Raise 1001, "VerifySettings() Sub", "Could Not Open Registry

    Key"Else

    If RegSetValueEx(hnd, sPortKey, 0, REG_SZ, ByVal sPortNum,Len(sPortNum)) Then

    Err.Raise 1001, "VerifySettings() Sub", "Could Not SetRegistry Key Port Value"

    End IfEnd If

    Exit Sub

    ErrTrap:MsgBox Err.Number & " " & Err.Description & vbCr & " Error Generated By "

    & Err.Source, vbCritical, _"System Error Trap !"End Sub

    Public Function BinaryToDecimal(Binary As String) As LongDim n As LongDim s As Integer

  • 8/8/2019 Acustic Sensors

    27/31

    27

    For s = 1 To Len(Binary)n = n + (Mid(Binary, Len(Binary) - s + 1, 1) * (2 ^ (s - 1)))Next s

    BinaryToDecimal = n

    End FunctionSub Pause(seconds As Integer)Const SECS_INDAY = 24! * 60 * 60 ' Seconds per dayDim start As Singlestart = TimerDo: Loop Until (Timer + SECS_INDAY - start) Mod SECS_INDAY >= seconds

    End Sub

    Module1.bas For logging and mapping

    Attribute VB_Name = "Module1"'These are the API functions that makes it all possible (to use BitBlt and otherfunctions)

    Public Declare Function BitBlt Lib "gdi32" (ByVal hDestDC As Long, ByVal X AsLong, ByVal Y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hSrcDCAs Long, ByVal xSrc As Long, ByVal ySrc As Long, ByVal dwRop As Long) As LongPublic Const SRCAND = &H8800C6Public Const SRCCOPY = &HCC0020Public Const SRCERASE = &H4400328Public Const SRCINVERT = &H660046Public Const SRCPAINT = &HEE0086

    Public Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)

    Sub SetLog(Message As String)Dim theFile As String, theMessage As StringtheFile = App.Path & "\data.txt"theMessage = Message & vbCrLfOpen theFile For Append As #1Print #1, theMessageClose #1End Sub

    Sub KillLog()On Error Resume NextKill App.Path & "\data.txt"On Error GoTo 0End Sub

    RegistryAPIs.bas Look for available serial ports.

    Attribute VB_Name = "RegistryAPIs"

    Option Explicit

    '-----------------------------------------------------------------------------------------------------------------------Public Const SYNCHRONIZE = &H100000

  • 8/8/2019 Acustic Sensors

    28/31

    28

    Public Const READ_CONTROL = &H20000

    Public Const STANDARD_RIGHTS_READ = (READ_CONTROL)

    Public Const STANDARD_RIGHTS_WRITE = (READ_CONTROL)

    Public Const STANDARD_RIGHTS_ALL = &H1F0000

    '-----------------------------------------------------------------------------------------------------------------------

    Public Const KEY_QUERY_VALUE = &H1Public Const KEY_ENUMERATE_SUB_KEYS = &H8

    Public Const KEY_NOTIFY = &H10

    Public Const KEY_SET_VALUE = &H2

    Public Const KEY_CREATE_SUB_KEY = &H4

    Public Const KEY_READ = ((READ_CONTROL Or KEY_QUERY_VALUE Or

    KEY_ENUMERATE_SUB_KEYS Or KEY_NOTIFY) And (Not SYNCHRONIZE))

    Public Const KEY_WRITE = ((STANDARD_RIGHTS_WRITE Or KEY_SET_VALUE Or

    KEY_CREATE_SUB_KEY) And (Not SYNCHRONIZE))

    '-----------------------------------------------------------------------------------------------------------------------

    Public Const ERROR_SUCCESS = 0&

    '-----------------------------------------------------------------------------------------------------------------------Public Const REG_SZ = 1

    Public Const REG_BINARY = 3

    Public Const REG_DWORD = 4

    '-----------------------------------------------------------------------------------------------------------------------

    Public Const HKEY_CLASSES_ROOT = &H80000000

    Public Const HKEY_CURRENT_USER = &H80000001

    Public Const HKEY_LOCAL_MACHINE = &H80000002

    Public Const HKEY_USERS = &H80000003

    Public Const HKEY_PERFORMANCE_DATA = &H80000004

    Public Const HKEY_CURRENT_CONFIG = &H80000005

    Public Const HKEY_DYN_DATA = &H80000006

    '-----------------------------------------------------------------------------------------------------------------------

    Public Const REG_CREATED_NEW_KEY = &H1

    Public Const REG_OPENED_EXISTING_KEY = &H2

    Public Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)

    '-----------------------------------------------------------------------------------------------------------------------

    Public Declare Function SleepEx Lib "kernel32" (ByVal dwMilliseconds As Long, ByVal bAlertable

    As Long) As Long

    '-----------------------------------------------------------------------------------------------------------------------

    Public Declare Function RegOpenKeyEx Lib "advapi32.dll" Alias "RegOpenKeyExA" (ByVal hKeyAs Long, ByVal lpSubKey As _

    String, ByVal ulOptions As Long, ByVal samDesired As Long, phkResult As Long) As Long

    '-----------------------------------------------------------------------------------------------------------------------

    Public Declare Function RegCloseKey Lib "advapi32.dll" (ByVal hKey As Long) As Long

    '-----------------------------------------------------------------------------------------------------------------------

    Public Declare Function RegQueryValueEx Lib "advapi32.dll" Alias "RegQueryValueExA" (ByVal

    hKey As Long, ByVal _

    lpValueName As String, ByVal lpReserved As Long, lpType As Long, lpData As Any, lpcbData As

    Long) As Long

    '-----------------------------------------------------------------------------------------------------------------------

    Public Declare Function RegCreateKeyEx Lib "advapi32.dll" Alias "RegCreateKeyExA" (ByValhKey As Long, ByVal lpSubKey _

  • 8/8/2019 Acustic Sensors

    29/31

    29

    As String, ByVal Reserved As Long, ByVal lpClass As Long, ByVal dwOptions As Long, ByVal

    samDesired As Long, ByVal _

    lpSecurityAttributes As Long, phkResult As Long, lpdwDisposition As Long) As Long

    '-----------------------------------------------------------------------------------------------------------------------

    Public Declare Function RegDeleteKey Lib "advapi32.dll" Alias "RegDeleteKeyA" (ByVal hKey As

    Long, ByVal lpSubKey As _String) As Long

    '-----------------------------------------------------------------------------------------------------------------------

    Public Declare Function RegSetValueEx Lib "advapi32.dll" Alias "RegSetValueExA" (ByVal hKey

    As Long, ByVal _

    lpValueName As String, ByVal Reserved As Long, ByVal dwType As Long, lpData As Any,

    ByVal cbData As Long) As Long

    '-----------------------------------------------------------------------------------------------------------------------

    Public Declare Function RegEnumKey Lib "advapi32.dll" Alias "RegEnumKeyA" (ByVal hKey As

    Long, ByVal dwIndex As Long, _

    ByVal lpName As String, ByVal cbName As Long) As Long

    '-----------------------------------------------------------------------------------------------------------------------Public Declare Function RegDeleteValue Lib "advapi32.dll" Alias "RegDeleteValueA" (ByVal hKey

    As Long, ByVal _

    lpValueName As String) As Long

    '-----------------------------------------------------------------------------------------------------------------------

    Public Declare Function RegEnumValue Lib "advapi32.dll" Alias "RegEnumValueA" (ByVal hKey

    As Long, ByVal dwIndex As _

    Long, ByVal lpValueName As String, lpcbValueName As Long, ByVal lpReserved As Long,

    lpType As Long, lpData As Any, _

    lpcbData As Long) As Long

    '-----------------------------------------------------------------------------------------------------------------------

    Public Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (dest As Any, Source As

    Any, ByVal numBytes As Long)

    '-----------------------------------------------------------------------------------------------------------------------

    Declare Function FormatMessage Lib "kernel32" Alias "FormatMessageA" (ByVal dwFlags As Long,

    lpSource As Any, ByVal _

    dwMessageId As Long, ByVal dwLanguageId As Long, ByVal lpBuffer As String, ByVal nSize As

    Long, Arguments As Long) _

    As Long

    '-----------------------------------------------------------------------------------------------------------------------

    Public Declare Sub keybd_event Lib "user32" (ByVal bVk As Byte, ByVal bScan As Byte, ByVal

    dwFlags As Long, _ByVal dwExtraInfo As Long)

    Public Const VK_CONTROL = &H11

    Public Const VK_C = &H43

    Public Const VK_V = &H56

    Public Const KEYEVENTF_KEYUP = &H2

    '-----------------------------------------------------------------------------------------------------------------------

    Type OSVERSIONINFO

    dwOSVersionInfoSize As Long

    dwMajorVersion As Long

    dwMinorVersion As LongdwBuildNumber As Long

    dwPlatformId As Long

  • 8/8/2019 Acustic Sensors

    30/31

    30

    szCSDVersion As String * 128

    End Type

    '-----------------------------------------------------------------------------------------------------------------------

    Public Const VER_PLATFORM_WIN32_NT = 2

    Public Const VER_PLATFORM_WIN32_WINDOWS = 1

    Public Const VER_PLATFORM_WIN32s = 0Public Declare Function GetVersionEx Lib "kernel32" Alias "GetVersionExA" (lpVersionInformation

    As OSVERSIONINFO) As _

    Long

    '----------------------------------------------------------------------------------------------------------------

    VIII.APPENDIX C: REFERENCES

    About Ultrasonic Sensors:

    1. www.robot-electronics.co.uk

    2. www.acroname.com/robotics/parts/R93-SRF04.html

    3. http://www.uoxray.uoregon.edu/polamod/

    4. http://www.pioneernet.net/johnc/als5ears.htm

    5. http://www.tntech.edu/me/courses/Canfield/me4370/6500.htm

    6. http://www.engr.udayton.edu/faculty/jloomis/ece445/topics/sonar/faq.html

    7. https://www.zagrosrobotics.com/sonar.htm

    8. http://www.robofolio.com/folio/sonar/

    9. http://www.arches.uga.edu/~dass/srf04.html

    10. http://www.kronosrobotics.com/an149/DAN149.htm

    11. http://www.rentron.com/remote_control/SRF04.htm12. http://www.junun.org/MarkIII/Info.jsp?item=23

    About PIC Microcontroller:

    1. www.microchip.com

    2. http://controls.ae.gatech.edu/gtar/electronics/

    3. http://www.mstracey.btinternet.co.uk/pictutorial/

    4. http://www.ic-prog.com/

    5. http://www.embedded.com/1999/9904/9904feat2.htm

    6. http://www.picallw.com/

    About Serial Communication:

    1. http://ohm.bu.edu/edf/info/serial_pinout.html

    2. http://www.lookrs232.com/rs232/history_rs232.htm

    3. http://vacuumfeedthru.com/tech_libr/rs-232-c.htm

    4. http://www.piclist.com/techref/microchip/16F877/rs232-cr.htm

    5. http://home.earthlink.net/~botronics/index/pickey.html

  • 8/8/2019 Acustic Sensors

    31/31

    IX. APPENDIX D: COST

    In all engineering projects one of the important criteria is the cost of project. We also show our budget.

    PART COST ( TL )

    3 * SRF04 sensors147.500.000 TL

    1* PIC 16f877 micocontroller8.000.000 TL

    Electronic Components( Max232 IC, 7805

    Voltage Regulator, XT, Capacitors,Resistors)6.000.000 TL

    PIC 16F877 JMD Programmer 35.000.000 TL

    TOTAL 196.000.000 TL