ble: Bluetooth Low Energy (BLE) peripherals

[ bsd3, library, program, unclassified ] [ Propose Tags ]

This package provides a Haskell API for writing Bluetooth Low Energy peripherals.


[Skip to Readme]

Modules

[Last Documentation]

  • Bluetooth
    • Internal
      • Bluetooth.Internal.DBus
      • Bluetooth.Internal.Device
      • Bluetooth.Internal.Errors
      • Bluetooth.Internal.HasInterface
      • Bluetooth.Internal.Interfaces
      • Bluetooth.Internal.Lenses
      • Bluetooth.Internal.Serialize
      • Bluetooth.Internal.Types
      • Bluetooth.Internal.Utils

Flags

Manual Flags

NameDescriptionDefault
bluez543

Bluez version 5.43 or greater

Disabled
hasbluez

Whether to run tests that require Bluez

Enabled
hasdbus

Whether to run tests that require DBus mocking

Disabled

Use -f <flag> to enable a flag, or -f -<flag> to disable that flag. More info

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 0.1.1.0, 0.1.2.0, 0.1.3.0, 0.2.0.0, 0.3.0.0, 0.3.1.0, 0.3.2.0, 0.3.2.1, 0.3.3.0, 0.3.4.0, 0.4.0.0, 0.4.1, 0.4.2
Dependencies base (>=4.8 && <4.10), ble, bytestring (>=0.10 && <0.11), cereal (>=0.4 && <0.6), containers (>=0.5 && <0.6), d-bus (>=0.1.5 && <0.2), data-default-class (>=0.0 && <0.2), hslogger, markdown-unlit, microlens (>=0.4 && <0.5), microlens-ghc (>=0.4 && <0.5), mtl (>=2.2 && <2.3), optparse-applicative (>=0.12 && <0.14), random (>=1 && <2), stm, text (>=1 && <2), transformers (>=0.4 && <0.6), uuid (>=1 && <2) [details]
License BSD-3-Clause
Copyright 2016 Julian K. Arni
Author Julian K. Arni
Maintainer jkarni@turingjump.com
Home page http://github.com/plow-technologies/ble#readme
Bug tracker https://github.com/plow-technologies/ble/issues
Source repo head: git clone https://github.com/plow-technologies/ble
Uploaded by jkarni at 2017-12-05T23:12:44Z
Distributions
Executables readme, hrs-client, hrs, auth
Downloads 10472 total (32 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs not available [build log]
All reported builds failed as of 2017-12-06 [all 3 reports]

Readme for ble-0.4.2

[back to package description]

ble - Bluetooth Low Energy for Haskell

ble is a Haskell library for writing Bluetooth Low Energy peripherals and centrals.

For usage, see the haddocks. There are also examples in examples directory.

Example

The code below is a simple example of a complete Bluetooth Low Energy application. The application allows a counter to be read, and adds one to the value of the counter, as well as allowing the counter to be set to any value.

module Main (main) where

import Bluetooth
import Control.Concurrent     (threadDelay)
import Control.Concurrent.STM
import Control.Monad.IO.Class

main :: IO ()
main = do
  ref <- newTVarIO 0
  conn <- connect
  x <- runBluetoothM (registerAndAdvertiseApplication $ app ref) conn
  case x of
    Right _ -> putStrLn "Started BLE counter application!"
    Left e -> error $ "Error starting application " ++ show e
  threadDelay maxBound

app :: TVar Int -> Application
app ref
  = "/com/turingjump/example/counter"
     & services .~ [counter ref]

counter :: TVar Int -> Service 'Local
counter ref
  = "4f1f704f-0a0b-49e4-bd27-6368f27697a7"
     & characteristics .~ [getCounter ref]

getCounter :: TVar Int -> CharacteristicBS 'Local
getCounter ref
  = "90874979-563e-4224-9da6-3b1a6c03e97d"
      & readValue  ?~ encodeRead readV
      & writeValue ?~ encodeWrite writeV
      & properties .~ [CPRead, CPWrite]
  where
    readV :: Handler Int
    readV = liftIO $ do
      v <- atomically $ modifyTVar' ref succ >> readTVar ref
      putStrLn $ "Value requested. New value: " ++ show v
      return v

    writeV :: Int -> Handler Bool
    writeV i = liftIO $ do
      v <- atomically $ swapTVar ref i
      putStrLn $ "Value changed to: " ++ show i
      putStrLn $ "Old value: " ++ show v
      return True

You can also write centrals (clients). See HeartRateClient in the examples directory.

Requirements

ble currently only supports Linux, and requires Bluez versions 5.41 and up. To see what version you are running, type:

bluetoothd --version

Note that for version 5.41 in particular you'll need to run bluetoothd with the experimental flag. (You might have to change /lib/systemd/system/bluetooth.service to add --experimental to the ExecStart command, and the restart the bluetoothd service)

Contributing

Note that quite a number of tests are protected by a flag (hasDBus). This is in part because of extra system dependencies; and in part because the tests require mocking DBus objects, which in turn require changing the dbus configuration files.

If you are contributing to this packages, you should run all tests (and possibly write further ones utilizing the mock infrastructure). You'll need to run:

sudo ./test/Mock/dbus-permissions.sh

And then reboot (yes, terrible, but DBus has trouble reloading its configuration).

You then need the python dependencies. Minimally, this will involve:

pip install -r test/Mock/requirements.txt

stack.yaml has the hasDBus flag set, so if you're using stack you'll by default be running all the tests.