News:

Let's find out together what makes a PIC Tick!

Main Menu

hmc5883 and hmc5983 proton basic compass codes

Started by dnaci, Feb 05, 2021, 05:13 PM

Previous topic - Next topic

dnaci

An inc file is also available to run the code.

Device = 18F2550
Declare Xtal = 20

Config_Start
FOSC = HS
MCLRE = On
PWRT = On
FCMEN = Off
IESO = Off
BOR = Off
VREGEN = Off
WDT = Off
PBADEN = Off
CCP2MX = Off
STVREN = Off
LVP = Off
XINST = Off
Debug = Off
Cp0 = Off
Cp1 = Off
Cp2 = Off
Cp3 = Off
CPB = Off
CPD = Off
WRT0 = Off
WRT1 = Off
WRT2 = Off
WRT3 = Off
WRTB = Off
WRTC = Off
WRTD = Off
EBTR0 = Off
EBTR1 = Off
EBTR2 = Off
EBTR3 = Off
EBTRB = Off
Config_End

Include "AtnFc.inc"
 
Declare LCD_DTPin PORTB.4
Declare LCD_RSPin PORTB.2
Declare LCD_ENPin PORTB.3
Declare LCD_Interface 4
Declare LCD_Lines 4
Declare LCD_Type 0
Declare LCD_CommandUs = 2000
Declare LCD_DataUs =50 ' or  255
     
Symbol SCL = PORTB.1
Symbol SDA = PORTB.0
 
Symbol X_MSB = $03 'Read Register, Output of X MSB 8-bit value.
Symbol X_LSB = $04 'Read Register, Output of X LSB 8-bit value.
Symbol Z_MSB = $05 'Read Register, Output of Z MSB 8-bit value.
Symbol Z_LSB = $06 'Read Register, Output of Z LSB 8-bit value.
Symbol Y_MSB = $07 'Read Register, Output of Y MSB 8-bit value.
Symbol Y_LSB = $08 'Read Register, Output of Y LSB 8-bit value.
 
Symbol WRITE_ADDRESS = $3C  ' Requests Write operation
Symbol READ_ADDRESS  = $3D  ' Requests Read operation
Symbol MODE = $02                   ' Mode setting register
Symbol I2C_VAL = $0
 
Dim X As SWord 'x sensor measured value
Dim Y As SWord 'y sensor measured value
Dim Z As SWord 'z sensor measured value
 
Dim XC As Float
Dim YC As Float

Dim Heading As Float
Dim DeclinationAngle As Float
Dim Pi As Float
Dim Pi2 As Float
     
Pi  = 3.141592654
Pi2 = 6.283185307 ; 2*pi
 
DelayMS 100
 
I2COut SDA,SCL, 0x3c, 0x00, [0x70] '(8-average, 15 Hz default, normal measurement)
I2COut SDA,SCL, 0x3c, 0x01, [0xA0] ' (Gain=5)
I2COut SDA,SCL, 0x3c, 0x02, [0x00] ' Send continuous output command

Cls

Main:
I2CIn SDA, SCL, $3D, $03,[X.HighByte ,X.LowByte,Z.HighByte,Z.LowByte,Y.HighByte,Y.LowByte]
XC = X      'Convert the numbers to Float
YC = Y      'Either Result will come garbage

ATan2(YC, XC, Heading)                    'Calculate the ATaan2
DeclinationAngle = 5.38                   'DeclinationAngle is different in every place. For the value of your location: https://www.magnetic-declination.com/
Heading = Heading + DeclinationAngle;
   
If Heading < 0 Then Heading = Heading + Pi2    'Add 2*Pi
If Heading > Pi2 Then Heading = Heading - Pi2  'Subtract 2*Pi
 
Heading = Heading * 57.295779        'Convert radians to degrees

Print At 1,1,"Head : ",Dec2 Heading," N   "

DelayMS 200
GoTo Main

AtnFc.inc file:
'-------------------------------------------------------------------------------------------------------------------------------------
' Name      : Atan2                                                       
' Purpose   : Computes the principal value of arc tangent of Y/X, using the
'           : signs of both the arguments to determine the quadrant of the return value
' Input     : PP_AARG holds the Y input
'           : PP_BARG holds the X input
' Output    : PP_AARG holds the arc tangent of Y/X.         
' Notes     : All values are in Radians
'
'
' Bring two of the compiler's floating point system variables into the program for the Atan2 macro
'
$ifndef __Atan2__

    Dim PP_AARG As Float System
    Dim PP_BARG As Float System
'-----------------------------------------------------------------------------------------------
    GoTo _Atan2_Main                              ' Jump over the subroutines
'-----------------------------------------------------------------------------------------------

$define ATan2(pYin, pXin, pResult) '
    PP_AARG = pYin '
    PP_BARG = pXin '
    _Atan2         '
    pResult = PP_AARG

_Atan2 Macro-
    GoSub __Atan2
Endm

#ifMacro- _Atan2
__Atan2:         
    Dim fYin As PP_AARG
    Dim fXin As PP_BARG
    Dim bQuadrant As Byte System
    Dim tSign As bQuadrant.7

    tSign = 0
    bQuadrant = 0

    If fYin <= 0.0 Then
        If fXin <= 0.0 Then
            bQuadrant = 3
        Else
            bQuadrant = 4
        EndIf
    ElseIf fXin < 0.0 Then
        bQuadrant = 2
    Else
        bQuadrant = 1
    EndIf

    If fYin < 0.0 Then
        tSign = 1
        fYin = Abs fYin
    EndIf
   
    fXin = Abs fXin
 
    If fXin = 0.0 Then
        PP_AARG = 1.570796325
        If tSign = 1 Then
            PP_AARG = -PP_AARG
        EndIf
    Else
        PP_AARG = fYin / fXin
        PP_AARG = ATan(PP_AARG)
        bQuadrant = bQuadrant & %01111111   ' Mask out the Sign bit
        Select bQuadrant
            Case 2
                PP_BARG = PP_AARG
                PP_AARG = 3.14159265 - PP_BARG
            Case 3
                PP_AARG = PP_AARG - 3.14159265
            Case 4
                PP_AARG = -PP_AARG
        EndSelect
    EndIf
    Return
#endIfMacro-


 _Atan2_Main:
$endif

keytapper

I suggest to format the relevant part in a procedure. This would expand the usage with a major number of MCU.
Ignorance comes with a cost

flosigud

I have somewhere a codefor HMC5883 with procedures. I will post it as soon as my Win 10 computer gets out of the boot loop. It runs on either 18F or 33FJ.

midali

I tested the code for 26k20 , but I have a trouble, the lcd show head only 349.81 N . Its something wrong in config PIC or in HMC5883 module ? Can somebody help me ?

Device 18F26K20
Declare Xtal = 4
Config_Start
'   FOSC = HS ; HS oscillator
'   FOSC = HSPLL ; HS oscillator, PLL enabled (Clock Frequency = 4 x FOSC1)
   FOSC = INTIO67 ; INTERNAL OSCILLATOR .PORTA.6 AND 7 I/O's
   FCMEN = OFF ; Fail-Safe Clock Monitor disabled
   IESO = OFF ; Oscillator Switchover mode disabled
   PWRT = OFF ; PWRT enabled
   BOREN = SBORDIS ; Brown-out Reset enabled and controlled by software (SBOREN is enabled)
   BORV = 18 ; VBOR set to 2.7 V nominal
   WDTEN = On ; WDT is controlled by SWDTEN bit of the WDTCON register
   MCLRE = OFF ; MCLR pin enabled, RE3 input pin disabled
   HFOFST = OFF ; The system clock is held off until the HF-INTOSC is stable.
   LPT1OSC = OFF ; Disabled, T1 operates in standard power mode.
   PBADEN = OFF ; PORTB<4:0> pins are configured as digital I/O on Reset
   STVREN = On ; Stack full/underflow will cause Reset
   LVP = OFF ; Single-Supply ICSP disabled
   XINST = OFF ; Instruction set extension and Indexed Addressing mode disabled (Legacy mode)
   Debug = OFF ; Background debugger disabled, RB6 and RB7 configured as general purpose I/O pins
   Cp0 = On ; Block 0 (000800-003FFFh) not code-protected
   CP1 = On ; Block 1 (004000-007FFFh) not code-protected
   CP2 = On ; Block 2 (008000-00BFFFh) not code-protected
   CP3 = On ; Block 3 (00C000-00FFFFh) not code-protected
   CPB = On ; Boot block (000000-0007FFh) not code-protected
   CPD = On ; Data EEPROM not code-protected
   WRT0 = OFF ; Block 0 (000800-003FFFh) not write-protected
   WRT1 = OFF ; Block 1 (004000-007FFFh) not write-protected
   WRT2 = OFF ; Block 2 (008000-00BFFFh) not write-protected
   WRT3 = OFF ; Block 3 (00C000-00FFFFh) not write-protected
   WRTB = OFF ; Boot block (000000-0007FFh) not write-protected
   WRTC = OFF ; Configuration registers (300000-3000FFh) not write-protected
   WRTD = OFF ; Data EEPROM not write-protected
   EBTR0 = OFF ; Block 0 (000800-003FFFh) not protected from table reads executed in other blocks
   EBTR1 = OFF ; Block 1 (004000-007FFFh) not protected from table reads executed in other blocks
   EBTR2 = OFF ; Block 2 (008000-00BFFFh) not protected from table reads executed in other blocks
   EBTR3 = OFF ; Block 3 (00C000-00FFFFh) not protected from table reads executed in other blocks
   EBTRB = OFF ; Boot block (000000-0007FFh) not protected from table reads executed in other blocks
Config_End

'    XTAL = 64      ' REQUIRES PLL  ' USE 16 MHz CRYSTAL & DECLARE: XTAL = 64
'    XTAL = 48      ' REQUIRES PLL  ' USE 12 MHz CRYSTAL & DECLARE: XTAL = 48
'    Xtal = 40      ' REQUIRES PLL  ' USE 10 MHz CRYSTAL & DECLARE: XTAL = 40
'    Xtal = 20
' XTAL = 16  'INTERNAL OSCILLATOR MUST BE 8 OR 16 FOR PLL, CONFIGURE OSCCON AND OSCTUNE FOR PLL

'UNCOMMENT FOR INTERNAL ONLY
OSCCON = %01010110  'INTERNAL OSCILLATOR
'OSCTUNE = %01000000 '%x1xxxxxx = PLL ENABLED  MUST BE 8 OR 16MHz IN OSCCON FOR PLL
                                                                                                                       
Include "AtnFc.inc" 
Include "lcd.bas"
     
Symbol SCL = PORTB.1
Symbol SDA = PORTB.0
 
Symbol X_MSB = $03 'Read Register, Output of X MSB 8-bit value.
Symbol X_LSB = $04 'Read Register, Output of X LSB 8-bit value.
Symbol Z_MSB = $05 'Read Register, Output of Z MSB 8-bit value.
Symbol Z_LSB = $06 'Read Register, Output of Z LSB 8-bit value.
Symbol Y_MSB = $07 'Read Register, Output of Y MSB 8-bit value.
Symbol Y_LSB = $08 'Read Register, Output of Y LSB 8-bit value.
 
Symbol WRITE_ADDRESS = $3C  ' Requests Write operation
Symbol READ_ADDRESS  = $3D  ' Requests Read operation
Symbol MODE = $02                   ' Mode setting register
Symbol I2C_VAL = $0
 
Dim X As SWord 'x sensor measured value
Dim Y As SWord 'y sensor measured value
Dim Z As SWord 'z sensor measured value
 
Dim XC As Float
Dim YC As Float

Dim Heading As Float
Dim DeclinationAngle As Float
Dim Pi As Float
Dim Pi2 As Float
     
Pi  = 3.141592654
Pi2 = 6.283185307 ; 2*pi
 
DelayMS 100
 
I2COut SDA,SCL, 0x3c, 0x00, [0x70] '(8-average, 15 Hz default, normal measurement)
I2COut SDA,SCL, 0x3c, 0x01, [0xA0] ' (Gain=5)
I2COut SDA,SCL, 0x3c, 0x02, [0x00] ' Send continuous output command

Cls

Main:
I2CIn SDA, SCL, $3D, $03,[X.HighByte ,X.LowByte,Z.HighByte,Z.LowByte,Y.HighByte,Y.LowByte]
XC = X      'Convert the numbers to Float
YC = Y      'Either Result will come garbage

ATan2(YC, XC, Heading)                    'Calculate the ATaan2
DeclinationAngle = 5.32                   'DeclinationAngle is different in every place. For the value of your location: https://www.magnetic-declination.com/
Heading = Heading + DeclinationAngle;
   
If Heading < 0 Then Heading = Heading + Pi2    'Add 2*Pi
If Heading > Pi2 Then Heading = Heading - Pi2  'Subtract 2*Pi
 
Heading = Heading * 57.295779        'Convert radians to degrees

Print At 1,1,"Head : ",Dec2 Heading," N   "

DelayMS 200
GoTo Main

broderic

Hello.
Some time ago I modified this code, using Amicus18 and HMC5883L, and I found it worked.
I remember that it was to be payed attention to the the type L of HMC, that needed different parameters in I2Cout.
I hope it can be of some help.

Regards





 I2COut SDAPin,SCLPin, 0x1A, 0x0B, [0x01] ' (Gain=5)
    I2COut SDAPin,SCLPin, 0x1A, 0x09, [0x1D] ' Send continuous output command
 
  DelayMS 40
 
main:

    I2CIn SDAPin, SCLPin, $1B, $00,[X.LowByte,X.HighByte,Y.LowByte,Y.HighByte,Z.LowByte,Z.HighByte]
    I2CIn SDAPin, SCLPin, $1B, $07,[T.LowByte,T.HighByte]
    T=(T/100)+42
    XC = X +191                                    ;Convert the numbers to Float
    YC = Y +975
    ATan2(YC, XC, heading)                        ;Calculate the ATaan2
    DeclinationAngle = 0.0457                    ;DeclinationAngle is different in every place
    heading = heading + DeclinationAngle
   
    If heading < 0 Then heading = heading + Pi2    ;Add 2*Pi
    If heading > Pi2 Then heading = heading - Pi2  ;Subtract 2*Pi
   
    heading = heading * 57.295779                  ;Convert radians to degrees
 
    GoSub Compass
    HRSOut  SDec Z,13,10
 
    DelayMS 200
    GoTo main

'------------------------------------
'            !
'------------------------------------
Compass:
 
   
     
    Print At 1,0, SDec T,"",27,"C"
   
    Print At 6,94, Dec1 heading
   
Return






towlerg

Quote from: flosigud on Feb 07, 2021, 12:52 AMI have somewhere a codefor HMC5883 with procedures. I will post it as soon as my Win 10 computer gets out of the boot loop. It runs on either 18F or 33FJ.
Not still in the loop, I hope. Did you ever find that code to post?

david

#6
Hi,
I found a very basic test of the raw sensor amongst my files.

'Mag sensor reader with hardware I2C  Needs pull-up resistors on clk, data lines   Current code

'                  Vdd <1 U 8> Gnd   
'                  RA5 <2   7> RA0  Spare I/O
'Direct To PC  TX  RA4 <3   6> RA1  SCL
'                  RA3 <4   5> RA2  SDA           


Device = 12F1840
Config1 FCMEN_OFF, IESO_OFF, CLKOUTEN_OFF, BOREN_OFF, CPD_OFF, CP_OFF, MCLRE_OFF, PWRTE_ON, WDTE_OFF, FOSC_INTOSC
Config2 LVP_OFF, BORV_19, STVREN_OFF, PLLEN_OFF, WRT_OFF


Declare Xtal = 16 'Internal OSC
OSCCON = %01111010    '16MHz=01111010, 4MHz=01101010, 8MHz =01110010
APFCON = %10000100    'Tx=RA.4
TRISA = %00000110     '

'***************** Serial port declares ********************************
Declare Hserial_Baud=9600
Declare Hserial_SPBRG=25
TXSTA=%00100000
BAUDCON=%01010000   'output direct to PC - no inverter
Declare Hserial_Clear=On
Declare Hbus_Bitrate 100    '100kHz or 400kHz

'*************  I2C comms set up  **************************************
SSPCON1=%00111000       'enable port, 7 bit address, master mode

'***********  Set up   *********************
Symbol MAG_W= %111100    'Device address and write
Symbol MAG_R= %111101    'Device address and read             

'**********   variables   ******************
Dim Setup As Byte
Dim MAGX As Word
Dim MAGY As Word
Dim MAGZ As Word

'initialize
        HBusOut MAG_W,[0,112]      'Write, Reg 0, 112  112=8avg, 15Hz rate
        HBusOut MAG_W,[1,0]      'Write, Reg 1, Gain 5=160   Gain 1 default=32  Gain 0=0 (highest)
       
        PORTA=0             '?
        DelayMS 1000        '?
        PORTA=0             '?

begin:       
        HBusOut MAG_W,[2,1]                  'Write, Reg 2, Single shot mode
        DelayMS 100                          'pointer auto increments
        HBusIn MAG_R,[MAGX, MAGZ, MAGY]      'returns 16 bit value of 3 mag axis
                       

'***************   output data   ****************************   
HRSOut  "X=",SDec MAGX,"  ","Y=",SDec MAGY, "  ","Z=",SDec MAGZ,"  ",10,13   '9600 direct.
DelayMS 600
GoTo begin

End



Cheers,
David

midali

Sorry for late , now I'm back to hobby and a have a free time to play with sensor.

The problem was from type L (HMC5883L) , was a different parameters in I2Cout.
Thank you all, especially Broderic and Dave !


flosigud

Quote from: towlerg on Jun 25, 2021, 08:50 AMNot still in the loop, I hope. Did you ever find that code to post?
Out of that loop, but there are others..

Below is the code. It is just something I got off the old site and tidied up a bit. Smells of Adafruit.
I didn't find a way to post a zip so:
'****************************************************************
' Name : UNTITLED.BAS
' Author : [Rony Chakraborty]
' Notice : Copyright (c) 2014 [www.ekushebangla.com]
' : All Rights Reserved
' Date : 10/12/2014
' Version : 1.0
' Notes :
' :
'****************************************************************

  Device 18F26K22

' Include "18fxxk22intosc64.Inc"
' Declare Hserial_Baud 115200
Declare Hbus_Bitrate 400
Declare PORTB_Pullups true
Include "AtnFc.inc"
'
'
' HMC5883 registers
' ----------------------------------------------------------------------------
'
Symbol HMC5883_CRA_REG = 0 ' Configuration_Register_A
Symbol HMC5883_CRB_REG = 1 ' Configuration_Register_B
Symbol HMC5883_MR_REG = 2 ' Mode_Register
Symbol HMC5883_OUT_X_H = 3 ' Data_Output_X_MSB_Register
Symbol HMC5883_OUT_X_L = 4 ' Data_Output_X_LSB_Register
Symbol HMC5883_OUT_Z_H = 5 ' Data_Output_Z_MSB_Register
Symbol HMC5883_OUT_Z_L = 6 ' Data_Output_Z_LSB_Register
Symbol HMC5883_OUT_Y_H = 7 ' Data_Output_Y_LSB_Register
Symbol HMC5883_OUT_Y_L = 8 ' Data_Output_Y_MSB_Register
Symbol HMC5883_SR_REG = 9 ' Status_Register_Read
Symbol HMC5883_IRA_REG = 10    ' Identification_Register_A
Symbol HMC5883_IRB_REG = 11 ' Identification_Register_B
Symbol HMC5883_IRC_REG = 12 ' Identification_Register_C
Symbol HMC5883_TEMP_OUT_H = $31 '
Symbol HMC5883_TEMP_OUT_L = $32 '


Symbol X_MSB = $03 ' Read Register, Output of X MSB 8-bit value.
Symbol X_LSB = $04 ' Read Register, Output of X LSB 8-bit value.
Symbol Z_MSB = $05 ' Read Register, Output of Z MSB 8-bit value.
Symbol Z_LSB = $06 ' Read Register, Output of Z LSB 8-bit value.
Symbol Y_MSB = $07 ' Read Register, Output of Y MSB 8-bit value.
Symbol Y_LSB = $08 ' Read Register, Output of Y LSB 8-bit value.

Symbol WRITE_ADDRESS = $3C ' Requests Write operation
Symbol READ_ADDRESS = $3D ' Requests Read operation
Symbol MODE = $02 ' Mode setting register
    Symbol Pi = 3.141592654
    Symbol Pi2 = 6.283185307
    Symbol DeclinationAngle = 13.233333333333333/57.295779
   
'
' HMC5883L_init()
' ----------------------------------------------------------------------------
'

Proc HMC5883L_init()
Global Dim X As SWord ' x sensor measured value
Global Dim Y As SWord ' y sensor measured value
Global Dim Z As SWord ' z sensor measured value' Global Dim YC As Float
Global Dim Heading As Float
HBusOut WRITE_ADDRESS, HMC5883_CRA_REG, [$70] ' (8-average, 15 Hz default, normal measurement)
HBusOut WRITE_ADDRESS, HMC5883_CRB_REG, [$A0] ' (Gain=5)
HBusOut WRITE_ADDRESS, HMC5883_MR_REG, [$00] ' Send continuous output command
EndProc

'
' GetHeading()
' ----------------------------------------------------------------------------
'
Proc GetHeading(), Float
HBusIn READ_ADDRESS, $03,[X.HighByte ,X.LowByte,Z.HighByte,Z.LowByte,Y.HighByte,Y.LowByte]
Dim XC As Float = X ' Convert the numbers to Float
Dim YC As Float = Y ' Else Result will be garbage
ATan2(YC, XC, Result) ' Calculate the ATan2
Result = Result + DeclinationAngle ' DeclinationAngle is different in every place
If Result < 0 Then Result = Result + Pi2 ' Add 2*Pi
If Result > Pi2 Then Result = Result - Pi2 ' Subtract 2*Pi
Result = Result * 57.295779 ' Convert radians to degrees
EndProc

' mainloop
' ----------------------------------------------------------------------------
'

HMC5883L_init()
DelayMS 200
Do
Heading = GetHeading()
 
HRSOut "Head : ",Dec Heading," N   ",13  

DelayMS 200
Loop