ble-0.3.4.0: Bluetooth Low Energy (BLE) peripherals

Safe HaskellNone
LanguageHaskell2010

Bluetooth.Internal.Types

Contents

Synopsis

Documentation

(</>) :: Text -> Text -> Text Source #

Append two Texts, keeping exactly one slash between them.

UUID

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 

Instances

Eq UUID Source # 

Methods

(==) :: UUID -> UUID -> Bool #

(/=) :: UUID -> UUID -> Bool #

Ord UUID Source # 

Methods

compare :: UUID -> UUID -> Ordering #

(<) :: UUID -> UUID -> Bool #

(<=) :: UUID -> UUID -> Bool #

(>) :: UUID -> UUID -> Bool #

(>=) :: UUID -> UUID -> Bool #

max :: UUID -> UUID -> UUID #

min :: UUID -> UUID -> UUID #

Show UUID Source # 

Methods

showsPrec :: Int -> UUID -> ShowS #

show :: UUID -> String #

showList :: [UUID] -> ShowS #

IsString UUID Source # 

Methods

fromString :: String -> UUID #

Generic UUID Source # 

Associated Types

type Rep UUID :: * -> * #

Methods

from :: UUID -> Rep UUID x #

to :: Rep UUID x -> UUID #

Representable UUID Source # 

Associated Types

type RepType UUID :: DBusType #

Random UUID Source # 

Methods

randomR :: RandomGen g => (UUID, UUID) -> g -> (UUID, g) #

random :: RandomGen g => g -> (UUID, g) #

randomRs :: RandomGen g => (UUID, UUID) -> g -> [UUID] #

randoms :: RandomGen g => g -> [UUID] #

randomRIO :: (UUID, UUID) -> IO UUID #

randomIO :: IO UUID #

HasUuid Service UUID Source # 
HasSolicitUUIDs Advertisement [UUID] Source # 
HasServiceUUIDs Advertisement [UUID] Source # 
HasServiceData Advertisement (Map UUID ByteString) Source # 
HasUuid (Characteristic typ0) UUID Source # 
type Rep UUID Source # 
type Rep UUID = D1 (MetaData "UUID" "Bluetooth.Internal.Types" "ble-0.3.4.0-FK43JGOfOYfLQ1e1O1Vx0V" False) (C1 (MetaCons "UUID" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UUID)))
type RepType UUID Source # 

Any

data Any where Source #

A Haskell existential type corresponding to DBus' Variant.

Constructors

MkAny :: forall a. Representable a => a -> Any 

Instances

data WithObjectPath a Source #

Instances

Functor WithObjectPath Source # 

Methods

fmap :: (a -> b) -> WithObjectPath a -> WithObjectPath b #

(<$) :: a -> WithObjectPath b -> WithObjectPath a #

Eq a => Eq (WithObjectPath a) Source # 
Show a => Show (WithObjectPath a) Source # 
Generic (WithObjectPath a) Source # 

Associated Types

type Rep (WithObjectPath a) :: * -> * #

Representable (WithObjectPath (Characteristic a)) Source # 
Representable (WithObjectPath Service) Source # 
HasValue (WithObjectPath a0) a0 Source # 

Methods

value :: Lens' (WithObjectPath a0) a0 Source #

HasPath (WithObjectPath a0) ObjectPath Source # 
HasInterface (WithObjectPath CharacteristicBS) GattCharacteristic Source # 
HasInterface (WithObjectPath CharacteristicBS) Properties Source # 
HasInterface (WithObjectPath Service) GattService Source # 
HasInterface (WithObjectPath Service) Properties Source # 
HasInterface (WithObjectPath Advertisement) LEAdvertisement Source # 
type Rep (WithObjectPath a) Source # 
type Rep (WithObjectPath a) = D1 (MetaData "WithObjectPath" "Bluetooth.Internal.Types" "ble-0.3.4.0-FK43JGOfOYfLQ1e1O1Vx0V" False) (C1 (MetaCons "WOP" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "withObjectPathPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ObjectPath)) (S1 (MetaSel (Just Symbol "withObjectPathValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))))
type RepType (WithObjectPath (Characteristic a)) Source # 
type RepType (WithObjectPath Service) Source # 

Method

Descriptor

data Descriptor Source #

Constructors

Descriptor 

Fields

Instances

Eq Descriptor Source # 
Show Descriptor Source # 
Generic Descriptor Source # 

Associated Types

type Rep Descriptor :: * -> * #

type Rep Descriptor Source # 
type Rep Descriptor = D1 (MetaData "Descriptor" "Bluetooth.Internal.Types" "ble-0.3.4.0-FK43JGOfOYfLQ1e1O1Vx0V" False) (C1 (MetaCons "Descriptor" PrefixI True) (S1 (MetaSel (Just Symbol "descriptorUuid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UUID)))

data AdvertisingPacketType Source #

Instances

Eq AdvertisingPacketType Source # 
Ord AdvertisingPacketType Source # 
Read AdvertisingPacketType Source # 
Show AdvertisingPacketType Source # 
Generic AdvertisingPacketType Source # 
type Rep AdvertisingPacketType Source # 
type Rep AdvertisingPacketType = D1 (MetaData "AdvertisingPacketType" "Bluetooth.Internal.Types" "ble-0.3.4.0-FK43JGOfOYfLQ1e1O1Vx0V" False) ((:+:) ((:+:) (C1 (MetaCons "ConnectableUndirected" PrefixI False) U1) (C1 (MetaCons "ConnectableDirected" PrefixI False) U1)) ((:+:) (C1 (MetaCons "NonConnnectableUndirected" PrefixI False) U1) (C1 (MetaCons "ScannableUndirected" PrefixI False) U1)))

Characteristic

data CharacteristicProperty Source #

Instances

Bounded CharacteristicProperty Source # 
Enum CharacteristicProperty Source # 
Eq CharacteristicProperty Source # 
Ord CharacteristicProperty Source # 
Read CharacteristicProperty Source # 
Show CharacteristicProperty Source # 
Generic CharacteristicProperty Source # 
Representable CharacteristicProperty Source # 
HasProperties (Characteristic typ0) [CharacteristicProperty] Source # 
type Rep CharacteristicProperty Source # 
type Rep CharacteristicProperty = D1 (MetaData "CharacteristicProperty" "Bluetooth.Internal.Types" "ble-0.3.4.0-FK43JGOfOYfLQ1e1O1Vx0V" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CPBroadcast" PrefixI False) U1) ((:+:) (C1 (MetaCons "CPRead" PrefixI False) U1) (C1 (MetaCons "CPEncryptRead" PrefixI False) U1))) ((:+:) (C1 (MetaCons "CPEncryptAuthenticatedRead" PrefixI False) U1) ((:+:) (C1 (MetaCons "CPWriteWithoutResponse" PrefixI False) U1) (C1 (MetaCons "CPWrite" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "CPEncryptWrite" PrefixI False) U1) ((:+:) (C1 (MetaCons "CPEncryptAuthenticatedWrite" PrefixI False) U1) (C1 (MetaCons "CPAuthenticatedSignedWrites" PrefixI False) U1))) ((:+:) (C1 (MetaCons "CPNotify" PrefixI False) U1) ((:+:) (C1 (MetaCons "CPIndicate" PrefixI False) U1) (C1 (MetaCons "CPSignedWriteCommand" PrefixI False) U1)))))
type RepType CharacteristicProperty Source # 

data CharacteristicOptions Source #

Instances

Eq CharacteristicOptions Source # 
Read CharacteristicOptions Source # 
Show CharacteristicOptions Source # 
Generic CharacteristicOptions Source # 
Representable CharacteristicOptions Source # 
HasOffset CharacteristicOptions (Maybe Word16) Source # 
type Rep CharacteristicOptions Source # 
type Rep CharacteristicOptions = D1 (MetaData "CharacteristicOptions" "Bluetooth.Internal.Types" "ble-0.3.4.0-FK43JGOfOYfLQ1e1O1Vx0V" False) (C1 (MetaCons "CharacteristicOptions" PrefixI True) (S1 (MetaSel (Just Symbol "characteristicOptionsOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Word16))))
type RepType CharacteristicOptions Source # 

data Characteristic typ Source #

Constructors

Characteristic 

Fields

Instances

HasCharacteristics Service [CharacteristicBS] Source # 
IsString (Characteristic a) Source # 
Generic (Characteristic typ) Source # 

Associated Types

type Rep (Characteristic typ) :: * -> * #

Methods

from :: Characteristic typ -> Rep (Characteristic typ) x #

to :: Rep (Characteristic typ) x -> Characteristic typ #

Representable (WithObjectPath (Characteristic a)) Source # 
HasUuid (Characteristic typ0) UUID Source # 
HasInterface (WithObjectPath CharacteristicBS) GattCharacteristic Source # 
HasInterface (WithObjectPath CharacteristicBS) Properties Source # 
HasWriteValue (Characteristic typ0) (Maybe (typ0 -> Handler Bool)) Source # 

Methods

writeValue :: Lens' (Characteristic typ0) (Maybe (typ0 -> Handler Bool)) Source #

HasReadValue (Characteristic typ0) (Maybe (Handler typ0)) Source # 

Methods

readValue :: Lens' (Characteristic typ0) (Maybe (Handler typ0)) Source #

HasProperties (Characteristic typ0) [CharacteristicProperty] Source # 
type Rep (Characteristic typ) Source # 
type Rep (Characteristic typ) = D1 (MetaData "Characteristic" "Bluetooth.Internal.Types" "ble-0.3.4.0-FK43JGOfOYfLQ1e1O1Vx0V" False) (C1 (MetaCons "Characteristic" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "characteristicUuid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UUID)) (S1 (MetaSel (Just Symbol "characteristicProperties") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [CharacteristicProperty]))) ((:*:) (S1 (MetaSel (Just Symbol "characteristicReadValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Handler typ)))) (S1 (MetaSel (Just Symbol "characteristicWriteValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (typ -> Handler Bool)))))))
type RepType (WithObjectPath (Characteristic a)) Source # 

Service

data Service Source #

Instances

IsString Service Source # 

Methods

fromString :: String -> Service #

Generic Service Source # 

Associated Types

type Rep Service :: * -> * #

Methods

from :: Service -> Rep Service x #

to :: Rep Service x -> Service #

HasUuid Service UUID Source # 
HasServices Application [Service] Source # 
HasCharacteristics Service [CharacteristicBS] Source # 
Representable (WithObjectPath Service) Source # 
HasInterface (WithObjectPath Service) GattService Source # 
HasInterface (WithObjectPath Service) Properties Source # 
type Rep Service Source # 
type Rep Service = D1 (MetaData "Service" "Bluetooth.Internal.Types" "ble-0.3.4.0-FK43JGOfOYfLQ1e1O1Vx0V" False) (C1 (MetaCons "Service" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "serviceUuid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UUID)) (S1 (MetaSel (Just Symbol "serviceCharacteristics") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [CharacteristicBS]))))
type RepType (WithObjectPath Service) Source # 

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.

Advertisement

data AdvertisementType Source #

Constructors

Broadcast 
Peripheral 

Instances

Bounded AdvertisementType Source # 
Enum AdvertisementType Source # 
Eq AdvertisementType Source # 
Read AdvertisementType Source # 
Show AdvertisementType Source # 
Generic AdvertisementType Source # 
Representable AdvertisementType Source # 
HasType_ Advertisement AdvertisementType Source # 
type Rep AdvertisementType Source # 
type Rep AdvertisementType = D1 (MetaData "AdvertisementType" "Bluetooth.Internal.Types" "ble-0.3.4.0-FK43JGOfOYfLQ1e1O1Vx0V" False) ((:+:) (C1 (MetaCons "Broadcast" PrefixI False) U1) (C1 (MetaCons "Peripheral" PrefixI False) U1))
type RepType AdvertisementType Source # 

data Advertisement Source #

An advertisement can be generated automatically with advertisementFor, or with the IsList instance. Both of these by default assume the advertisement is for a peripheral.

You can also, of course, use the constructor.

Instances

IsList Advertisement Source # 
Eq Advertisement Source # 
Show Advertisement Source # 
Generic Advertisement Source # 

Associated Types

type Rep Advertisement :: * -> * #

Representable Advertisement Source # 
Default Advertisement Source # 

Methods

def :: Advertisement #

HasType_ Advertisement AdvertisementType Source # 
HasIncludeTxPower Advertisement Bool Source # 
HasInterface Advertisement Properties Source # 
HasSolicitUUIDs Advertisement [UUID] Source # 
HasServiceUUIDs Advertisement [UUID] Source # 
HasServiceData Advertisement (Map UUID ByteString) Source # 
HasManufacturerData Advertisement (Map Word16 ByteString) Source # 
HasInterface (WithObjectPath Advertisement) LEAdvertisement Source # 
type Rep Advertisement Source # 
type Rep Advertisement = D1 (MetaData "Advertisement" "Bluetooth.Internal.Types" "ble-0.3.4.0-FK43JGOfOYfLQ1e1O1Vx0V" False) (C1 (MetaCons "Advertisement" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "advertisementType_") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AdvertisementType)) ((:*:) (S1 (MetaSel (Just Symbol "advertisementServiceUUIDs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [UUID])) (S1 (MetaSel (Just Symbol "advertisementSolicitUUIDs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [UUID])))) ((:*:) (S1 (MetaSel (Just Symbol "advertisementManufacturerData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Word16 ByteString))) ((:*:) (S1 (MetaSel (Just Symbol "advertisementServiceData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map UUID ByteString))) (S1 (MetaSel (Just Symbol "advertisementIncludeTxPower") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))))
type Item Advertisement Source # 
type RepType Advertisement Source # 

Connection

connectionName :: Connection -> Text Source #

The unique DBus connection name, Useful for monitoring activity with 'dbus-monitor'. For information on how to setup dbus-monitor for debugging, see DebuggingDBus.

Since: 0.1.3.0

connect :: IO Connection Source #

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

BluetoothM

data Error Source #

Instances

Show Error Source # 

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

IsString Error Source # 

Methods

fromString :: String -> Error #

Generic Error Source # 

Associated Types

type Rep Error :: * -> * #

Methods

from :: Error -> Rep Error x #

to :: Rep Error x -> Error #

MonadError Error BluetoothM Source # 
type Rep Error Source # 
type Rep Error = D1 (MetaData "Error" "Bluetooth.Internal.Types" "ble-0.3.4.0-FK43JGOfOYfLQ1e1O1Vx0V" False) ((:+:) (C1 (MetaCons "DBusError" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MethodError))) (C1 (MetaCons "BLEError" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))

Assorted

newtype ApplicationRegistered Source #

This datatype, which is kept opaque, is returned when an application is successfully registered, and required as an argument from functions that should only be called after the application has been registered.

data Status Source #

Constructors

Success 
Failure 

Instances

Enum Status Source # 
Eq Status Source # 

Methods

(==) :: Status -> Status -> Bool #

(/=) :: Status -> Status -> Bool #

Ord Status Source # 
Read Status Source # 
Show Status Source # 
Generic Status Source # 

Associated Types

type Rep Status :: * -> * #

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

type Rep Status Source # 
type Rep Status = D1 (MetaData "Status" "Bluetooth.Internal.Types" "ble-0.3.4.0-FK43JGOfOYfLQ1e1O1Vx0V" False) ((:+:) (C1 (MetaCons "Success" PrefixI False) U1) (C1 (MetaCons "Failure" PrefixI False) U1))