vrpn-0.3.0.0: Bindings to VRPN.

Copyright(c) 2015-19 Brian W Bush
LicenseMIT
MaintainerBrian W Bush <code@functionally.io>
StabilityStable
PortabilityLinux
Safe HaskellSafe
LanguageHaskell2010

Network.VRPN

Contents

Description

Bindings to VRPN, <https://github.com/vrpn/vrpn/wiki>, and is loosely modeled on the code in <https://github.com/vrpn/vrpn/blob/master/client_src/vrpn_print_devices.C>. This has been tested using VRPN 07.30 on Linux. It requires the VRPN C++ header files.

Here is a simple example that illustrates the use of this module:

data ButtonType = LeftButton | RightButton
  deriving (Enum, Eq, Show)

main :: IO ()
main =
  do
    putStrLn "Press the left button to exit."
    done <- newEmptyMVar
    let
      -- A remote button that signals completion when the left button is released.
      button :: Device Int ButtonType Double
      button =
        Button "spacenav0@localhost"
          $ Just
          $ time button state ->
            do
              print (time, button, state)
              if button == LeftButton && not state
                then void $ tryPutMVar done ()
                else return ()
      -- An analog device.
      analog :: Device Int Int Int Double
      analog = Analog "spacenav0@localhost"
        $ Just
        $ curry print
    -- Open the remote devices.
    devices <- sequence [openDevice button, openDevice analog]
    -- Loop until a signal to complete is received.
    mainLoops (not $ isEmptyMVar done) 10 devices
    -- Close the remote devices.
    mapM_ closeDevice devices

Synopsis

Devices

data Device s b d a Source #

A VRPN device.

Constructors

Tracker

A tracker.

Fields

Button

A button.

Fields

Analog

An analog device.

Fields

Dial

A dial.

Fields

data RemoteDevice Source #

A remote VRPN device.

Callbacks

type PositionCallback s a Source #

Arguments

 = TimeVal

The timestamp.

-> s

Which sensor is reporting.

-> (a, a, a)

The position vector.

-> (a, a, a, a)

The orientation quaternion.

-> IO ()

The action performed by the callback.

Callback for position information.

type VelocityCallback s a Source #

Arguments

 = TimeVal

The timestamp.

-> s

Which sensor is reporting.

-> (a, a, a)

The velocity vector.

-> (a, a, a, a)

The future orientation quaternion.

-> a

Delta time for the future orientation quaternion, in seconds.

-> IO ()

The action performed by the callback.

Callback for velocity information.

type AccelerationCallback s a Source #

Arguments

 = TimeVal

The timestamp.

-> s

Which sensor is reporting.

-> (a, a, a)

The acceleration vector.

-> (a, a, a, a)

The acceleration orientation quaternion.

-> a

Delta time for the acceleration quaternion, in seconds.

-> IO ()

The action performed by the callback.

Callback for acceleration information.

type ButtonCallback b Source #

Arguments

 = TimeVal

The timestamp.

-> b

Which button was pressed, counting from 0.

-> Bool

Whether the button is pressed.

-> IO ()

The action performed by the callback.

Callback for button information.

type AnalogCallback a Source #

Arguments

 = TimeVal

The timestamp.

-> [a]

The analog values.

-> IO ()

The action performed by the callback.

Callback for analog information.

type DialCallback d a Source #

Arguments

 = TimeVal

The timestamp.

-> d

Which dial changed.

-> a

The fraction of a revolution it changed.

-> IO ()

The action performed by the callback.

Callback for dial information.

type ExitCallback Source #

Arguments

 = IO Bool

An action indicate whether to exit the main loop.

Callback for exiting the main loop.

Operations on devices

openDevice Source #

Arguments

:: (Enum s, Enum b, Enum d, RealFloat a) 
=> Device s b d a

The device.

-> IO RemoteDevice

An action for opening the device.

Open a remote VRPN device.

closeDevice Source #

Arguments

:: RemoteDevice

The device.

-> IO ()

An action for closing the device.

Close a remote device.

withDevices Source #

Arguments

:: (Enum s, Enum b, Enum d, RealFloat a) 
=> [Device s b d a]

The devices.

-> ([RemoteDevice] -> IO ())

The operation.

-> IO ()

The action for operating on the devices.

Operate on devices.

mainLoop Source #

Arguments

:: RemoteDevice

The device.

-> IO ()

An action for running the main loop of the device *once*.

Run the main loop of a device *once*.

mainLoops Source #

Arguments

:: RealFloat a 
=> ExitCallback

Callback for exiting the loop.

-> a

The number of milliseconds to idle after each device's main loop is run once.

-> [RemoteDevice]

The devices.

-> IO ()

An action for running the main loops *repeatedly*.

Run the main loops of devices *repeatedly*.

Time

data TimeVal Source #

Timestamps in seconds and fractions of a section.

Constructors

TimeVal 

Fields

sleep Source #

Arguments

:: RealFloat a 
=> a

The number of milliseconds.

-> IO ()

An action to sleep the specified amount of time

Sleep for the specified amount of time.