Multifunction DAQ

cancel
Showing results for 
Search instead for 
Did you mean: 

write single da-value from VBA to 6221

Hello,
All I need is to output as single digital value to an analog output
 
aka: write "Dev1/ad0",-3,2
 
the problem: do it from a ms-access (VBA),
just can't find the examples to get it working,
 
trying simplistic code:
Public Function test3()
  Dim l, k As Long
  Dim s As String
  Dim a As Integer
  l = 3
 
  k = DAQmx.DAQmxCreateAOVoltageChan(l, "Dev1/ao0", "aoChannel", _
  CDbl(-5), CDbl(5), DAQmx_Val_VoltageUnits2_Volts, "")
  MsgBox k
  'set val
  a = 25000
  'a(1) = 100
  k = DAQmx.DAQmxWriteRaw(l, 1, True, CLng(10), a, 1, "")
  MsgBox k
End Function
 
 
get errorcode -200088,
 
 
Really need a really simple solution here, and fast.
Can't belive I'm provided with 2 cd:s and no examples regarding neither
VB (<>.NET) or Delphi.
 
Please reply ASAP.
(with basic code),
 
Yours sincerely,
T eriksson
0 Kudos
Message 1 of 4
(3,370 Views)
Ok, solved.
 
Just a skeleton, here we go:
 
 
Dim sampsPerChanWritten As Long
Dim test As Long
Dim taskHandle As Long
Dim delay As Double
'OBS Long, fel i exempel
Dim status As Long
Public Sub DAQmxErrChk(errorCode As Long)
'   Utility function to handle errors by recording the DAQmx error code
'   and message. This sub, (c) NI
    Dim errorString As String
    Dim bufferSize As Long
    Dim status As Long
    If (errorCode < 0) Then
        ' Find out the error message length.
        bufferSize = DAQmxGetErrorString(errorCode, 0, 0)
        ' Allocate enough space in the string.
        errorString = String$(bufferSize, 0)
        ' Get the actual error message.
        status = DAQmxGetErrorString(errorCode, errorString, bufferSize)
        ' Trim it to the actual length, and display the message
        errorString = Left(errorString, InStr(errorString, Chr$(0)))
        Err.Raise errorCode, , errorString
    End If
End Sub

Private Sub Configure_Port_Click()
    Dim numChannels As Long
    Dim errorCode As Long
    Dim errorString As String
    DAQmxErrChk DAQmxCreateTask("", taskHandle)
    DAQmxErrChk DAQmxCreateAOVoltageChan(taskHandle, "Dev1/ao0", "aoChannel", -10, 10, DAQmx_Val_VoltageUnits2_Volts, "")
    DAQmxErrChk DAQmxGetTaskNumChans(taskHandle, numChannels)
    If numChannels > 1 Then
      errorCode = -1
      errorString = "Please spec. only one channel."
      Err.Raise errorCode, , errorString
    End If
End Sub
Private Sub Stop_Task_Click()
  DAQmxErrChk DAQmxStopTask(taskHandle)
  DAQmxErrChk DAQmxClearTask(taskHandle)
End Sub
Private Sub Write_Logic_0_Click()
    'Set the DA to -4V. The # is equiv to cdbl(-4)
    DAQmxErrChk DAQmxWriteAnalogScalarF64(taskHandle, True, 10#, -4#, ByVal 0&)
End Sub
Private Sub Write_Logic_1_Click()
    'Set it to +7.
    DAQmxErrChk DAQmxWriteAnalogScalarF64(taskHandle, True, 10#, 7#, ByVal 0&)
End Sub
 
0 Kudos
Message 2 of 4
(3,339 Views)
Smileys? That's just too much...
 
Should be
    DAQmxErrChk DAQmxWriteAnalogScalarF64(taskHandle, True, 10#, -4#, B-y-V-a-l- -0-&-)
0 Kudos
Message 3 of 4
(3,338 Views)
On 4 Dec, 14:40, tomjoad <x...@no.email> wrote:
> Hello,
> All I need is to output as single digital value to an analog output
> &nbsp;
> aka: write "Dev1/ad0",-3,2
> &nbsp;
> the problem: do it from a ms-access (VBA),
> just can't find the examples to get it working,
> &nbsp;
> trying simplistic code:
> Public Function test3()&nbsp; Dim l, k As Long&nbsp; Dim s As String&nbsp; Dim a As Integer&nbsp; l = 3&nbsp; &nbsp; k = DAQmx.DAQmxCreateAOVoltageChan(l, "Dev1/ao0", "aoChannel", _&nbsp; CDbl(-5), CDbl(5), DAQmx_Val_VoltageUnits2_Volts, "")&nbsp; MsgBox k&nbsp; 'set val&nbsp; a = 25000&nbsp; 'a(1) = 100&nbsp; k = DAQmx.DAQmxWriteRaw(l, 1, True, CLng(10), a, 1, "")&nbsp; MsgBox kEnd Function
> &nbsp;
> &nbsp;
> get errorcode -200088,
> &nbsp;
> &nbsp;
> Really need a really simple solution here, and fast.
> Can't belive I'm provided with 2 cd:s and no examples regarding neither
> VB (&lt;&gt;.NET) or Delphi.
> &nbsp;
> Please reply ASAP.
> (with basic code),
> &nbsp;
> Yours sincerely,
> T eriksson

Solved here:
http://forums.ni.com/ni/board/message?board.id=250&thread.id=35426
0 Kudos
Message 4 of 4
(3,334 Views)