ble-0.1.0.0: Bluetooth Low Energy (BLE) peripherals

Safe HaskellNone
LanguageHaskell2010

Bluetooth

Contents

Description

This module exports all you should need to build a Bluetooth Low Energy (BLE) peripheral.

The core concepts involved are:

Application
This contains the entirety of your application, and is composed of zero or more Services.
Service
A set of zero or more conceptually related Characteristics. Identified by it's UUID.
Characteristic
Characteristics represent the actual data of your application. They may allow reading, writing, and subscribing. Also identified by it's UUID.
Advertisement
This describes how an application will advertise itself to other BLE devices.

All three have IsString instances and lens field accessors. The recommended way of using this library is by using the OverloadedStrings pragma and lenses. A complete example can be found here.

{-# LANGUAGE OverloadedStrings #-}
import Bluetooth
import Control.Concurrent (threadDelay)

app :: Application
app = "/com/turingjump/example" & services .~ [aService]

aService :: Service
aService = "d0bc6707-e9a5-4c85-8d22-d73d33f0330c"
    & characteristics .~ [aCharacteristic]

aCharacteristic :: CharacteristicBS
aCharacteristic = "b3170df6-1770-4d60-86db-a487534cbcc3"
    & readValue ?~ encodeRead (return (32::Int))
    & properties .~ [CPRead]

main :: IO ()
main = do
  conn <- connect
  runBluetoothM (registerAndAdverstiseApplication app) conn
  threadDelay maxBound

Synopsis

Documentation

registerApplication :: Application -> BluetoothM () Source

Registers an application (set of services) with Bluez.

registerAndAdvertiseApplication :: Application -> BluetoothM () Source

Registers an application and advertises it. If you would like to have finer-grained control of the advertisement, use registerApplication and advertise.

advertise :: WithObjectPath Advertisement -> BluetoothM () Source

Advertise a set of services.

advertisementFor :: Application -> WithObjectPath Advertisement Source

Create an advertisement for all of an application's services. The advertisement will be for peripheral (not broadcast) by default.

connect :: IO Connection Source

Creates a connection to DBus. This does *not* represent Bluetooth connection.

Field lenses

uuid :: HasUuid s a => Lens' s a Source

path :: HasPath s a => Lens' s a Source

type_ :: HasType_ s a => Lens' s a Source

value :: HasValue s a => Lens' s a Source

Updating values with notification

writeChrc :: Serialize x => WithObjectPath CharacteristicBS -> x -> BluetoothM Bool Source

Write a characteristic (if possible). Returns True if characterstic was successfully written.

BLE Types

Types representing components of a BLE application.

data Application Source

An application. Can be created from it's IsString instance. The string (application path) is used only for the DBus API, and will not have relevance within Bluetooth.

data UUID Source

UUIDs, used for services and characteristics.

Unofficial UUIDs will have 128-bits, and will look this:

d45e83fb-c772-459e-91a8-43cbf1443af4

Official UUIDs will have either 32 or 16 bits.

See ITU-T Rec. X.677 for more information on the format and generation of these UUIDs. You can use the Online UUID Generator to generate UUIDs.

Constructors

UUID UUID 

Encoding and decoding

Helpers for readValue and writeValue.

Handler

Handler err is a monad that allows the errors in the type-level list err.

Handler error classes

class ThrowsFailed m where Source

Methods

errFailed :: m a Source

Re-exports

module Lens.Micro