Safe Haskell | None |
---|---|
Language | Haskell2010 |
Bluetooth.Internal.Types
- (</>) :: Text -> Text -> Text
- parentPath :: Text -> Text
- data UUID = UUID UUID
- baseUUID :: String
- data Any where
- MkAny :: forall a. Representable a => a -> Any
- data WithObjectPath a = WOP {}
- class HasPath s a | s -> a where
- class HasValue s a | s -> a where
- type AnyDBusDict = TypeDict TypeString TypeVariant
- data Descriptor = Descriptor {}
- data AdvertisingPacketType
- data CharacteristicProperty
- chrPropPairs :: [(CharacteristicProperty, Text)]
- data CharacteristicOptions = CharacteristicOptions {}
- class HasOffset s a | s -> a where
- type CharacteristicBS = Characteristic ByteString
- data Characteristic typ = Characteristic {}
- class HasNotifying s a | s -> a where
- class HasProperties s a | s -> a where
- properties :: Lens' s a
- class HasReadValue s a | s -> a where
- class HasUuid s a | s -> a where
- class HasWriteValue s a | s -> a where
- writeValue :: Lens' s a
- characteristicObjectPath :: ObjectPath -> Int -> ObjectPath
- data Service = Service {}
- class HasCharacteristics s a | s -> a where
- characteristics :: Lens' s a
- data Application = Application {}
- class HasServices s a | s -> a where
- serviceObjectPath :: ObjectPath -> Int -> ObjectPath
- data AdvertisementType
- data Advertisement = Advertisement {}
- class HasIncludeTxPower s a | s -> a where
- includeTxPower :: Lens' s a
- class HasManufacturerData s a | s -> a where
- manufacturerData :: Lens' s a
- class HasServiceData s a | s -> a where
- serviceData :: Lens' s a
- class HasServiceUUIDs s a | s -> a where
- serviceUUIDs :: Lens' s a
- class HasSolicitUUIDs s a | s -> a where
- solicitUUIDs :: Lens' s a
- class HasType_ s a | s -> a where
- data Connection = Connection {
- dbusConn :: DBusConnection
- addObject :: ObjectPath -> Object -> IO ()
- connect :: IO Connection
- newtype BluetoothM a = BluetoothM (ReaderT Connection (ExceptT MethodError IO) a)
- runBluetoothM :: BluetoothM a -> Connection -> IO (Either MethodError a)
- toBluetoothM :: (Connection -> IO (Either MethodError a)) -> BluetoothM a
Documentation
parentPath :: Text -> Text Source
UUID
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.
Instances
Any
A Haskell existential type corresponding to DBus' Variant
.
Constructors
MkAny :: forall a. Representable a => a -> Any |
Instances
Representable Any Source | |
type RepType Any = TypeVariant Source |
data WithObjectPath a Source
Constructors
WOP | |
Fields |
Instances
class HasValue s a | s -> a where Source
Instances
HasValue (WithObjectPath a) a Source |
Method
Descriptor
Characteristic
data CharacteristicProperty Source
Constructors
Instances
chrPropPairs :: [(CharacteristicProperty, Text)] Source
data CharacteristicOptions Source
Constructors
CharacteristicOptions | |
Fields |
Instances
data Characteristic typ Source
Constructors
Characteristic | |
Fields
|
Instances
HasCharacteristics Service [CharacteristicBS] Source | |
IsString (Characteristic a) Source | |
Generic (Characteristic typ) Source | |
Representable (WithObjectPath (Characteristic a)) Source | |
HasUuid (Characteristic typ) UUID Source | |
HasInterface (WithObjectPath CharacteristicBS) GattCharacteristic Source | |
HasInterface (WithObjectPath CharacteristicBS) Properties Source | |
HasWriteValue (Characteristic typ) (Maybe (typ -> WriteValueM Bool)) Source | |
HasReadValue (Characteristic typ) (Maybe (ReadValueM typ)) Source | |
HasProperties (Characteristic typ) [CharacteristicProperty] Source | |
HasNotifying (Characteristic typ) (Maybe (IORef Bool)) Source | |
type Rep (Characteristic typ) Source | |
type RepType (WithObjectPath (Characteristic a)) = AnyDBusDict Source |
class HasNotifying s a | s -> a where Source
Instances
HasNotifying (Characteristic typ) (Maybe (IORef Bool)) Source |
class HasReadValue s a | s -> a where Source
Instances
HasReadValue (Characteristic typ) (Maybe (ReadValueM typ)) Source |
class HasWriteValue s a | s -> a where Source
Methods
writeValue :: Lens' s a Source
Instances
HasWriteValue (Characteristic typ) (Maybe (typ -> WriteValueM Bool)) Source |
Service
Constructors
Service | |
Fields |
Instances
class HasCharacteristics s a | s -> a where Source
Methods
characteristics :: Lens' s a Source
Instances
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.
Constructors
Application | |
Fields |
Instances
class HasServices s a | s -> a where Source
Instances
serviceObjectPath :: ObjectPath -> Int -> ObjectPath Source
Advertisement
data AdvertisementType Source
Constructors
Broadcast | |
Peripheral |
Instances
data Advertisement Source
Constructors
Advertisement | |
Instances
class HasManufacturerData s a | s -> a where Source
Methods
manufacturerData :: Lens' s a Source
Instances
Connection
data Connection Source
Constructors
Connection | |
Fields
|
Instances
connect :: IO Connection Source
Creates a connection to DBus. This does *not* represent Bluetooth connection.
BluetoothM
newtype BluetoothM a Source
Constructors
BluetoothM (ReaderT Connection (ExceptT MethodError IO) a) |
runBluetoothM :: BluetoothM a -> Connection -> IO (Either MethodError a) Source
toBluetoothM :: (Connection -> IO (Either MethodError a)) -> BluetoothM a Source