| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
BGLib.Types
Documentation
Instances
Instances
newtype UInt8Array Source #
Constructors
| UInt8Array | |
Fields | |
Instances
| Eq UInt8Array Source # | |
Defined in BGLib.Types | |
| Ord UInt8Array Source # | |
Defined in BGLib.Types Methods compare :: UInt8Array -> UInt8Array -> Ordering # (<) :: UInt8Array -> UInt8Array -> Bool # (<=) :: UInt8Array -> UInt8Array -> Bool # (>) :: UInt8Array -> UInt8Array -> Bool # (>=) :: UInt8Array -> UInt8Array -> Bool # max :: UInt8Array -> UInt8Array -> UInt8Array # min :: UInt8Array -> UInt8Array -> UInt8Array # | |
| Show UInt8Array Source # | |
Defined in BGLib.Types Methods showsPrec :: Int -> UInt8Array -> ShowS # show :: UInt8Array -> String # showList :: [UInt8Array] -> ShowS # | |
| IsString UInt8Array Source # | |
Defined in BGLib.Types Methods fromString :: String -> UInt8Array # | |
| Binary UInt8Array Source # | |
Defined in BGLib.Types | |
toUInt8Array :: ByteString -> UInt8Array Source #
data BgMessageType Source #
Constructors
| BgMsgCR | |
| BgMsgEvent |
Instances
| Bounded BgMessageType Source # | |
Defined in BGLib.Types | |
| Enum BgMessageType Source # | |
Defined in BGLib.Types Methods succ :: BgMessageType -> BgMessageType # pred :: BgMessageType -> BgMessageType # toEnum :: Int -> BgMessageType # fromEnum :: BgMessageType -> Int # enumFrom :: BgMessageType -> [BgMessageType] # enumFromThen :: BgMessageType -> BgMessageType -> [BgMessageType] # enumFromTo :: BgMessageType -> BgMessageType -> [BgMessageType] # enumFromThenTo :: BgMessageType -> BgMessageType -> BgMessageType -> [BgMessageType] # | |
| Eq BgMessageType Source # | |
Defined in BGLib.Types Methods (==) :: BgMessageType -> BgMessageType -> Bool # (/=) :: BgMessageType -> BgMessageType -> Bool # | |
| Show BgMessageType Source # | |
Defined in BGLib.Types Methods showsPrec :: Int -> BgMessageType -> ShowS # show :: BgMessageType -> String # showList :: [BgMessageType] -> ShowS # | |
data BgTecnologyType Source #
Instances
| Bounded BgTecnologyType Source # | |
Defined in BGLib.Types | |
| Enum BgTecnologyType Source # | |
Defined in BGLib.Types Methods succ :: BgTecnologyType -> BgTecnologyType # pred :: BgTecnologyType -> BgTecnologyType # toEnum :: Int -> BgTecnologyType # fromEnum :: BgTecnologyType -> Int # enumFrom :: BgTecnologyType -> [BgTecnologyType] # enumFromThen :: BgTecnologyType -> BgTecnologyType -> [BgTecnologyType] # enumFromTo :: BgTecnologyType -> BgTecnologyType -> [BgTecnologyType] # enumFromThenTo :: BgTecnologyType -> BgTecnologyType -> BgTecnologyType -> [BgTecnologyType] # | |
| Eq BgTecnologyType Source # | |
Defined in BGLib.Types Methods (==) :: BgTecnologyType -> BgTecnologyType -> Bool # (/=) :: BgTecnologyType -> BgTecnologyType -> Bool # | |
| Show BgTecnologyType Source # | |
Defined in BGLib.Types Methods showsPrec :: Int -> BgTecnologyType -> ShowS # show :: BgTecnologyType -> String # showList :: [BgTecnologyType] -> ShowS # | |
data BgCommandClass Source #
Constructors
| BgClsSystem | |
| BgClsPersistentStore | |
| BgClsAttributeDatabase | |
| BgClsConnection | |
| BgClsAttributeClient | |
| BgClsSecurityManager | |
| BgClsGenericAccessProfile | |
| BgClsHardware | |
| BgClsTest | |
| BgClsDfu |
Instances
| Bounded BgCommandClass Source # | |
Defined in BGLib.Types | |
| Enum BgCommandClass Source # | |
Defined in BGLib.Types Methods succ :: BgCommandClass -> BgCommandClass # pred :: BgCommandClass -> BgCommandClass # toEnum :: Int -> BgCommandClass # fromEnum :: BgCommandClass -> Int # enumFrom :: BgCommandClass -> [BgCommandClass] # enumFromThen :: BgCommandClass -> BgCommandClass -> [BgCommandClass] # enumFromTo :: BgCommandClass -> BgCommandClass -> [BgCommandClass] # enumFromThenTo :: BgCommandClass -> BgCommandClass -> BgCommandClass -> [BgCommandClass] # | |
| Eq BgCommandClass Source # | |
Defined in BGLib.Types Methods (==) :: BgCommandClass -> BgCommandClass -> Bool # (/=) :: BgCommandClass -> BgCommandClass -> Bool # | |
| Show BgCommandClass Source # | |
Defined in BGLib.Types Methods showsPrec :: Int -> BgCommandClass -> ShowS # show :: BgCommandClass -> String # showList :: [BgCommandClass] -> ShowS # | |
data BgPacketHeader Source #
Constructors
| BgPacketHeader | |
Fields | |
Instances
| Eq BgPacketHeader Source # | |
Defined in BGLib.Types Methods (==) :: BgPacketHeader -> BgPacketHeader -> Bool # (/=) :: BgPacketHeader -> BgPacketHeader -> Bool # | |
| Show BgPacketHeader Source # | |
Defined in BGLib.Types Methods showsPrec :: Int -> BgPacketHeader -> ShowS # show :: BgPacketHeader -> String # showList :: [BgPacketHeader] -> ShowS # | |
| Binary BgPacketHeader Source # | |
Defined in BGLib.Types Methods put :: BgPacketHeader -> Put # get :: Get BgPacketHeader # putList :: [BgPacketHeader] -> Put # | |
bgHeaderMatches :: BgMessageType -> BgTecnologyType -> BgCommandClass -> UInt8 -> BgPacketHeader -> Bool Source #
Instances
fromBgPayload :: BgPayload -> ByteString Source #
toBgPayload :: ByteString -> BgPayload Source #
Constructors
| BgPacket | |
Fields | |
class HasSerialPort env where Source #
Methods
getSerialPort :: env -> SerialPort Source #
askSerialPort :: (MonadReader env m, HasSerialPort env) => m SerialPort Source #
askDupBGChan :: (MonadIO m, MonadReader env m, HasBGChan env) => m (TChan BgPacket) Source #
askCloneBGChan :: (MonadIO m, MonadReader env m, HasBGChan env) => m (TChan BgPacket) Source #
packetBlock :: (MonadIO m, MonadReader env m, HasBGChan env) => m a -> m a Source #
packetBlock_ :: (MonadIO m, MonadReader env m, HasBGChan env) => m a -> m () Source #
packetBlock' :: (MonadIO m, MonadReader env m, HasBGChan env) => m a -> m a Source #
packetBlock'_ :: (MonadIO m, MonadReader env m, HasBGChan env) => m a -> m () Source #
bsShowHex :: ByteString -> String Source #
data RebootMode Source #
Constructors
| RebootNormal | |
| RebootDfu |
Instances
| Enum RebootMode Source # | |
Defined in BGLib.Types Methods succ :: RebootMode -> RebootMode # pred :: RebootMode -> RebootMode # toEnum :: Int -> RebootMode # fromEnum :: RebootMode -> Int # enumFrom :: RebootMode -> [RebootMode] # enumFromThen :: RebootMode -> RebootMode -> [RebootMode] # enumFromTo :: RebootMode -> RebootMode -> [RebootMode] # enumFromThenTo :: RebootMode -> RebootMode -> RebootMode -> [RebootMode] # | |
| Eq RebootMode Source # | |
Defined in BGLib.Types | |
| Show RebootMode Source # | |
Defined in BGLib.Types Methods showsPrec :: Int -> RebootMode -> ShowS # show :: RebootMode -> String # showList :: [RebootMode] -> ShowS # | |
| Binary RebootMode Source # | |
Defined in BGLib.Types | |
data AttributeValueType Source #
Constructors
| AVTRead | |
| AVTNotify | |
| AVTIndicate | |
| AVTReadByType | |
| AVTReadBlob | |
| AVTIndicateRsqReq |
Instances
data AttributeChangeReason Source #
Constructors
| ACRWriteRequest | |
| ACRWriteCommand | |
| ACRWriteRequestUser |
Instances
fASIndicate :: UInt8 Source #
fCConnected :: UInt8 Source #
fCEncrypted :: UInt8 Source #
fCCompleted :: UInt8 Source #
data GapAdvType Source #
Constructors
| GATNone | |
| GATFlags | |
| GATServices16bitMore | |
| GATServices16bitAll | |
| GATServices32bitMore | |
| GATServices32bitAll | |
| GATServices128bitMore | |
| GATServices128bitAll | |
| GATLocalnameShort | |
| GATLocalnameComplete | |
| GATTxPower |
Instances
| Enum GapAdvType Source # | |
Defined in BGLib.Types Methods succ :: GapAdvType -> GapAdvType # pred :: GapAdvType -> GapAdvType # toEnum :: Int -> GapAdvType # fromEnum :: GapAdvType -> Int # enumFrom :: GapAdvType -> [GapAdvType] # enumFromThen :: GapAdvType -> GapAdvType -> [GapAdvType] # enumFromTo :: GapAdvType -> GapAdvType -> [GapAdvType] # enumFromThenTo :: GapAdvType -> GapAdvType -> GapAdvType -> [GapAdvType] # | |
| Eq GapAdvType Source # | |
Defined in BGLib.Types | |
| Show GapAdvType Source # | |
Defined in BGLib.Types Methods showsPrec :: Int -> GapAdvType -> ShowS # show :: GapAdvType -> String # showList :: [GapAdvType] -> ShowS # | |
| Binary GapAdvType Source # | |
Defined in BGLib.Types | |
data GapAdvPolicy Source #
Constructors
| GAPAll | |
| GAPWhitelistScan | |
| GAPWhitelistConnect | |
| GAPWhitelistAll |
Instances
| Enum GapAdvPolicy Source # | |
Defined in BGLib.Types Methods succ :: GapAdvPolicy -> GapAdvPolicy # pred :: GapAdvPolicy -> GapAdvPolicy # toEnum :: Int -> GapAdvPolicy # fromEnum :: GapAdvPolicy -> Int # enumFrom :: GapAdvPolicy -> [GapAdvPolicy] # enumFromThen :: GapAdvPolicy -> GapAdvPolicy -> [GapAdvPolicy] # enumFromTo :: GapAdvPolicy -> GapAdvPolicy -> [GapAdvPolicy] # enumFromThenTo :: GapAdvPolicy -> GapAdvPolicy -> GapAdvPolicy -> [GapAdvPolicy] # | |
| Eq GapAdvPolicy Source # | |
Defined in BGLib.Types | |
| Show GapAdvPolicy Source # | |
Defined in BGLib.Types Methods showsPrec :: Int -> GapAdvPolicy -> ShowS # show :: GapAdvPolicy -> String # showList :: [GapAdvPolicy] -> ShowS # | |
| Binary GapAdvPolicy Source # | |
Defined in BGLib.Types | |
data GapAddressType Source #
Instances
| Enum GapAddressType Source # | |
Defined in BGLib.Types Methods succ :: GapAddressType -> GapAddressType # pred :: GapAddressType -> GapAddressType # toEnum :: Int -> GapAddressType # fromEnum :: GapAddressType -> Int # enumFrom :: GapAddressType -> [GapAddressType] # enumFromThen :: GapAddressType -> GapAddressType -> [GapAddressType] # enumFromTo :: GapAddressType -> GapAddressType -> [GapAddressType] # enumFromThenTo :: GapAddressType -> GapAddressType -> GapAddressType -> [GapAddressType] # | |
| Eq GapAddressType Source # | |
Defined in BGLib.Types Methods (==) :: GapAddressType -> GapAddressType -> Bool # (/=) :: GapAddressType -> GapAddressType -> Bool # | |
| Show GapAddressType Source # | |
Defined in BGLib.Types Methods showsPrec :: Int -> GapAddressType -> ShowS # show :: GapAddressType -> String # showList :: [GapAddressType] -> ShowS # | |
| Binary GapAddressType Source # | |
Defined in BGLib.Types Methods put :: GapAddressType -> Put # get :: Get GapAddressType # putList :: [GapAddressType] -> Put # | |
data GapConnectableMode Source #
Constructors
| GCMNonConnectable | |
| GCMDirectedConnectable | |
| GCMUndirectedConnectable | |
| GCMScannableNonConnectable |
Instances
data GapDiscoverableMode Source #
Constructors
| GDMNonDiscoverable | |
| GDMLimitedDiscoverable | |
| GDMGeneralDiscoverable | |
| GDMBroadcast | |
| GDMUserData | |
| GDMEnhancedBroadcasting |
Instances
data GapDiscoverMode Source #
Instances
data GSPScanHeaderFlag Source #
Constructors
| GSHFAdvInd | |
| GSHFAdvDirectInd | |
| GSHFAdvNonConnInd | |
| GSHFScanReq | |
| GSHFScanRsp | |
| GSHFConnectReq | |
| GSHFAdvDiscoverInd |
Instances
data GapScanPolicy Source #
Constructors
| GSPAll | |
| GSPWhitelist |
Instances
| Enum GapScanPolicy Source # | |
Defined in BGLib.Types Methods succ :: GapScanPolicy -> GapScanPolicy # pred :: GapScanPolicy -> GapScanPolicy # toEnum :: Int -> GapScanPolicy # fromEnum :: GapScanPolicy -> Int # enumFrom :: GapScanPolicy -> [GapScanPolicy] # enumFromThen :: GapScanPolicy -> GapScanPolicy -> [GapScanPolicy] # enumFromTo :: GapScanPolicy -> GapScanPolicy -> [GapScanPolicy] # enumFromThenTo :: GapScanPolicy -> GapScanPolicy -> GapScanPolicy -> [GapScanPolicy] # | |
| Eq GapScanPolicy Source # | |
Defined in BGLib.Types Methods (==) :: GapScanPolicy -> GapScanPolicy -> Bool # (/=) :: GapScanPolicy -> GapScanPolicy -> Bool # | |
| Show GapScanPolicy Source # | |
Defined in BGLib.Types Methods showsPrec :: Int -> GapScanPolicy -> ShowS # show :: GapScanPolicy -> String # showList :: [GapScanPolicy] -> ShowS # | |
| Binary GapScanPolicy Source # | |
Defined in BGLib.Types | |
fBKEDIVRAND :: UInt8 Source #
fBKMasterId :: UInt8 Source #
data SMIOCapabilities Source #
Instances
data SystemEndpoint Source #
Instances
| Enum SystemEndpoint Source # | |
Defined in BGLib.Types Methods succ :: SystemEndpoint -> SystemEndpoint # pred :: SystemEndpoint -> SystemEndpoint # toEnum :: Int -> SystemEndpoint # fromEnum :: SystemEndpoint -> Int # enumFrom :: SystemEndpoint -> [SystemEndpoint] # enumFromThen :: SystemEndpoint -> SystemEndpoint -> [SystemEndpoint] # enumFromTo :: SystemEndpoint -> SystemEndpoint -> [SystemEndpoint] # enumFromThenTo :: SystemEndpoint -> SystemEndpoint -> SystemEndpoint -> [SystemEndpoint] # | |
| Eq SystemEndpoint Source # | |
Defined in BGLib.Types Methods (==) :: SystemEndpoint -> SystemEndpoint -> Bool # (/=) :: SystemEndpoint -> SystemEndpoint -> Bool # | |
| Show SystemEndpoint Source # | |
Defined in BGLib.Types Methods showsPrec :: Int -> SystemEndpoint -> ShowS # show :: SystemEndpoint -> String # showList :: [SystemEndpoint] -> ShowS # | |
| Binary SystemEndpoint Source # | |
Defined in BGLib.Types Methods put :: SystemEndpoint -> Put # get :: Get SystemEndpoint # putList :: [SystemEndpoint] -> Put # | |
Constructors