Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
General Notes
Strictness
Record values are generally strict.
Haskell Types
We're not using and C types when it would be user-facing. Texts are
encoded/decoded as Text
. Numeric types are converted to
Int
, unless it's about actual payload data (attributes and
commands), where the appropriately sized types are used.
Generally speaking, we convert spectrum types to Haskell lists
(a vector would have been an option, and maybe we add that
possibility, too, if the need arises) and image types to the
Image
type which, again, uses lists intenally.
IO
The higher-level functions in this module are in MonadIO
instead
of just IO
so you can easily use them in your monad transformer
stacks.
Errors
Errors are thrown as exceptions of type TangoException
. User errors (such as reading a string attribute with a "read int" function) are thrown via error
instead.
Properties
The property retrieval API for Tango is elaborate, supporting different data types. We condensed this down to retrieving lists of strings. Conversion needs to happen on the Haskell side for now.
Examples
Reading and writing a scalar, boolean attribute
{-# LANGUAGE BlockArguments #-} {-# LANGUAGE OverloadedStrings #-} module Main where import Tango.Client main = case parseTangoUrl "sys/tg_test/1" of Left e -> error "couldn't resolve tango URL" Right deviceAddress -> withDeviceProxy deviceAddress \proxy -> do booleanResult <- readBoolAttribute proxy (AttributeName "boolean_scalar") putStrLn $ "boolean_scalar is " <> show (tangoValueRead booleanResult) writeBoolAttribute proxy (AttributeName "boolean_scalar") True
Reading a spectrum string attribute
{-# LANGUAGE BlockArguments #-} {-# LANGUAGE OverloadedStrings #-} module Main where import Tango.Client import qualified Data.Text.IO as TIO main = case parseTangoUrl "sys/tg_test/1" of Left e -> error "couldn't resolve tango URL" Right deviceAddress -> withDeviceProxy deviceAddress \proxy -> do result <- readBoolSpectrumAttribute proxy (AttributeName "string_spectrum_ro") mapM_ TIO.putStrLn result
Synopsis
- data DeviceProxy
- data TangoUrl
- newtype Milliseconds = Milliseconds Int
- parseTangoUrl :: Text -> Either Text TangoUrl
- withDeviceProxy :: forall m a. MonadUnliftIO m => TangoUrl -> (DeviceProxy -> m a) -> m a
- newDeviceProxy :: forall m. MonadUnliftIO m => TangoUrl -> m DeviceProxy
- deleteDeviceProxy :: forall m. MonadUnliftIO m => DeviceProxy -> m ()
- newtype TangoException = TangoException [DevFailed Text]
- data ErrSeverity
- data DevFailed a = DevFailed !a !a !a !ErrSeverity
- devFailedDesc :: DevFailed a -> a
- devFailedReason :: DevFailed a -> a
- devFailedOrigin :: DevFailed a -> a
- devFailedSeverity :: DevFailed a -> ErrSeverity
- newtype AttributeName = AttributeName Text
- data AttributeInfo = AttributeInfo !HaskellAttrWriteType !HaskellDataFormat !HaskellTangoDataType !Int !Int !Text !Text !Text !Text !Text !Text !Text !Text !Text !Text !Text !HaskellDispLevel [Text] Text !TangoAttrMemorizedType
- getConfigsForAttributes :: forall m. MonadUnliftIO m => DeviceProxy -> [AttributeName] -> m [AttributeInfo]
- getConfigForAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m AttributeInfo
- data TangoValue a = TangoValue {
- tangoValueRead :: a
- tangoValueWrite :: a
- data Image a = Image {
- imageContent :: ![a]
- imageDimX :: !Int
- imageDimY :: !Int
- data TangoAttrMemorizedType
- readIntegralAttribute :: forall m i. (MonadUnliftIO m, Integral i, Show i) => DeviceProxy -> AttributeName -> m (TangoValue i)
- readIntegralImageAttribute :: (MonadUnliftIO m, Integral i, Show i) => DeviceProxy -> AttributeName -> m (TangoValue (Image i))
- readIntegralSpectrumAttribute :: (MonadUnliftIO m, Integral i, Show i) => DeviceProxy -> AttributeName -> m (TangoValue [i])
- readRealAttribute :: forall m i. (MonadUnliftIO m, Fractional i, Show i) => DeviceProxy -> AttributeName -> m (TangoValue i)
- readRealImageAttribute :: (MonadUnliftIO m, Fractional i, Show i) => DeviceProxy -> AttributeName -> m (TangoValue (Image i))
- readRealSpectrumAttribute :: (MonadUnliftIO m, Fractional i, Show i) => DeviceProxy -> AttributeName -> m (TangoValue [i])
- writeIntegralAttribute :: (MonadUnliftIO m, Integral i) => DeviceProxy -> AttributeName -> i -> m ()
- writeIntegralImageAttribute :: (MonadUnliftIO m, Integral i) => DeviceProxy -> AttributeName -> Image i -> m ()
- writeIntegralSpectrumAttribute :: (MonadUnliftIO m, Integral i) => DeviceProxy -> AttributeName -> [i] -> m ()
- writeRealAttribute :: (MonadUnliftIO m, Real i) => DeviceProxy -> AttributeName -> i -> m ()
- writeRealImageAttribute :: (MonadUnliftIO m, Real i) => DeviceProxy -> AttributeName -> Image i -> m ()
- writeRealSpectrumAttribute :: (MonadUnliftIO m, Real i) => DeviceProxy -> AttributeName -> [i] -> m ()
- readBoolAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue Bool)
- readBoolImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image Bool))
- readBoolSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [Bool])
- readDoubleAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue Double)
- readDoubleImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image Double))
- readDoubleSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [Double])
- readEnumAttribute :: (MonadUnliftIO m, Enum t) => DeviceProxy -> AttributeName -> m (TangoValue t)
- readEnumImageAttribute :: (MonadUnliftIO m, Enum t) => DeviceProxy -> AttributeName -> m (TangoValue (Image t))
- readEnumSpectrumAttribute :: (MonadUnliftIO m, Enum t) => DeviceProxy -> AttributeName -> m (TangoValue [t])
- readFloatAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue Double)
- readFloatImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image Double))
- readFloatSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [Double])
- readLong64Attribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue Int64)
- readLong64ImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image Int64))
- readLong64SpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [Int64])
- readLongAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue Int64)
- readLongImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image Int64))
- readLongSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [Int64])
- readShortAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue Int16)
- readShortImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image Int16))
- readShortSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [Int16])
- readStateAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue HaskellTangoDevState)
- readStateImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image HaskellTangoDevState))
- readStateSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [HaskellTangoDevState])
- readStringAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue Text)
- readStringImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image Text))
- readStringSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [Text])
- readULong64Attribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue Word64)
- readULong64ImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image Word64))
- readULong64SpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [Word64])
- readULongAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue Word64)
- readULongImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image Word64))
- readULongSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [Word64])
- readUShortAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue Word16)
- readUShortImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image Word16))
- readUShortSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [Word16])
- writeBoolAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Bool -> m ()
- writeBoolImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image Bool -> m ()
- writeBoolSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [Bool] -> m ()
- writeDoubleAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Double -> m ()
- writeDoubleImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image Double -> m ()
- writeDoubleSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [Double] -> m ()
- writeEnumAttribute :: (MonadUnliftIO m, Enum t) => DeviceProxy -> AttributeName -> t -> m ()
- writeEnumImageAttribute :: (MonadUnliftIO m, Enum t) => DeviceProxy -> AttributeName -> Image t -> m ()
- writeEnumSpectrumAttribute :: (MonadUnliftIO m, Enum t) => DeviceProxy -> AttributeName -> [t] -> m ()
- writeFloatAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Double -> m ()
- writeFloatImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image Double -> m ()
- writeFloatSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [Double] -> m ()
- writeLong64Attribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Int64 -> m ()
- writeLong64ImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image Int64 -> m ()
- writeLong64SpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [Int64] -> m ()
- writeLongAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Int64 -> m ()
- writeLongImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image Int64 -> m ()
- writeLongSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [Int64] -> m ()
- writeShortAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Int16 -> m ()
- writeShortImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image Int16 -> m ()
- writeShortSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [Int16] -> m ()
- writeStateAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> HaskellTangoDevState -> m ()
- writeStateImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image HaskellTangoDevState -> m ()
- writeStateSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [HaskellTangoDevState] -> m ()
- writeStringAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Text -> m ()
- writeStringImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image Text -> m ()
- writeStringSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [Text] -> m ()
- writeULong64Attribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Word64 -> m ()
- writeULong64ImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image Word64 -> m ()
- writeULong64SpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [Word64] -> m ()
- writeULongAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Word64 -> m ()
- writeULongImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image Word64 -> m ()
- writeULongSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [Word64] -> m ()
- writeUShortAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Word16 -> m ()
- writeUShortImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image Word16 -> m ()
- writeUShortSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [Word16] -> m ()
- newtype CommandName = CommandName Text
- data DisplayLevel
- commandInVoidOutVoid :: MonadUnliftIO m => DeviceProxy -> CommandName -> m ()
- data CommandData
- = CommandVoid
- | CommandBool !Bool
- | CommandShort !Int16
- | CommandUShort !Word16
- | CommandInt32 !Int32
- | CommandInt64 !Int64
- | CommandWord64 !Word64
- | CommandFloat !Float
- | CommandDouble !Double
- | CommandString !Text
- | CommandState !HaskellTangoDevState
- | CommandEnum !Int16
- | CommandListBool ![Bool]
- | CommandListShort ![Int16]
- | CommandListUShort ![Word16]
- | CommandListInt64 ![Int64]
- | CommandListWord64 ![Word64]
- | CommandListLong64 ![Int64]
- | CommandListULong64 ![Word64]
- | CommandListFloat ![Float]
- | CommandListDouble ![Double]
- | CommandListString ![Text]
- | CommandListState ![HaskellTangoDevState]
- commandInOutGeneric :: MonadUnliftIO m => DeviceProxy -> CommandName -> CommandData -> m CommandData
- commandInEnumOutGeneric :: (MonadUnliftIO m, Enum t) => DeviceProxy -> CommandName -> t -> m CommandData
- commandInGenericOutEnum :: (MonadUnliftIO m, Enum t) => DeviceProxy -> CommandName -> CommandData -> m t
- commandInEnumOutEnum :: (MonadUnliftIO m, Enum t, Enum u) => DeviceProxy -> CommandName -> u -> m t
- commandListQuery :: MonadUnliftIO m => DeviceProxy -> m [CommandInfo]
- commandQuery :: MonadUnliftIO m => DeviceProxy -> CommandName -> m CommandInfo
- data CommandInfo = CommandInfo {}
- data Property = Property {
- propertyName :: !Text
- propertyIsEmpty :: !Bool
- propertyWrongDataType :: !Bool
- propertyData :: ![Text]
- newtype PropertyName = PropertyName Text
- getDeviceProperties :: forall m. MonadUnliftIO m => DeviceProxy -> [PropertyName] -> m [Property]
- putDeviceProperties :: forall m. MonadUnliftIO m => DeviceProxy -> [(PropertyName, [Text])] -> m ()
- deleteDeviceProperties :: forall m. MonadUnliftIO m => DeviceProxy -> [PropertyName] -> m ()
- data HaskellTangoDevState
- subscribeEvent :: forall m. MonadUnliftIO m => DeviceProxy -> AttributeName -> EventType -> Bool -> EventCallback m -> m SubscribedEvent
- unsubscribeEvent :: MonadUnliftIO m => DeviceProxy -> SubscribedEvent -> m ()
- withSubscribedEvent :: MonadUnliftIO m => DeviceProxy -> AttributeName -> EventType -> Bool -> EventCallback m -> m () -> m ()
- data SubscribedEvent
- data EventType
- type DatabaseProxy = DatabaseProxyPtr
- createDatabaseProxy :: MonadUnliftIO m => m DatabaseProxy
- deleteDatabaseProxy :: MonadUnliftIO m => DatabaseProxy -> m ()
- withDatabaseProxy :: MonadUnliftIO m => (DatabaseProxy -> m a) -> m a
- databaseSearchByDeviceName :: MonadUnliftIO m => DatabaseProxy -> Text -> m [Text]
- databaseSearchByClass :: MonadUnliftIO m => DatabaseProxy -> Text -> m [Text]
- databaseSearchObjectsByName :: MonadUnliftIO m => DatabaseProxy -> Text -> m [Text]
- databaseSearchObjectPropertiesByName :: MonadUnliftIO m => DatabaseProxy -> Text -> Text -> m [Text]
- lockDevice :: MonadUnliftIO m => DeviceProxy -> m ()
- unlockDevice :: MonadUnliftIO m => DeviceProxy -> m ()
- getAttributeNames :: MonadUnliftIO m => DeviceProxy -> m [AttributeName]
- withLocked :: MonadUnliftIO m => DeviceProxy -> m () -> m ()
- setTimeout :: MonadUnliftIO m => DeviceProxy -> Milliseconds -> m ()
- getTimeout :: MonadUnliftIO m => DeviceProxy -> m Milliseconds
- pollCommand :: MonadUnliftIO m => DeviceProxy -> CommandName -> Milliseconds -> m ()
- stopPollCommand :: MonadUnliftIO m => DeviceProxy -> CommandName -> m ()
- pollAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Milliseconds -> m ()
- stopPollAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m ()
Basics and initialization
To ensure proper cleanup, you should prefer the withDeviceProxy
function to initialize a proxy to a device, and then do something with it.
data DeviceProxy Source #
Wraps a pointer to a device proxy
Newtype wrapper around a Tango URL like tango://host:port/foo/bar/baz
. Retrieve via parseTangoUrl
newtype Milliseconds Source #
Newtype wrapper around milliseconds to make the raw numbers a bit more readable
Instances
Show Milliseconds Source # | |
Defined in Tango.Client showsPrec :: Int -> Milliseconds -> ShowS # show :: Milliseconds -> String # showList :: [Milliseconds] -> ShowS # |
parseTangoUrl :: Text -> Either Text TangoUrl Source #
Try to parse a Tango URL like tango://host:port/foo/bar/baz
(the left side of the Either
will be an error message)
withDeviceProxy :: forall m a. MonadUnliftIO m => TangoUrl -> (DeviceProxy -> m a) -> m a Source #
Safely initialize and clean up a device proxy for a given tango URL
newDeviceProxy :: forall m. MonadUnliftIO m => TangoUrl -> m DeviceProxy Source #
Create a new device proxy (check deleteDeviceProxy
and withDeviceProxy
, too)
deleteDeviceProxy :: forall m. MonadUnliftIO m => DeviceProxy -> m () Source #
Delete a device proxy (check newDeviceProxy
and withDeviceProxy
, too)
newtype TangoException Source #
This wraps the Tango exception trace in Haskell
Instances
Exception TangoException Source # | |
Defined in Tango.Client | |
Show TangoException Source # | |
Defined in Tango.Client showsPrec :: Int -> TangoException -> ShowS # show :: TangoException -> String # showList :: [TangoException] -> ShowS # |
data ErrSeverity Source #
How severe is the error (used in the Tango error types)
Instances
Wraps one piece of a Tango error trace (usually you will have lists of DevFailed
records). This is a generic to make treating its fields easier with respect to Text
and CString
(it's also a Functor
and Traversable
and all that for that reason)
DevFailed !a !a !a !ErrSeverity |
Instances
devFailedDesc :: DevFailed a -> a Source #
Failure description; this will usually be the actual error message you're interested in and will be human-readable
devFailedReason :: DevFailed a -> a Source #
Failure reason; this is usually an error code string, like API_AttrNotFound
devFailedOrigin :: DevFailed a -> a Source #
Failure origin: this is usually the C++ function that caused the error
devFailedSeverity :: DevFailed a -> ErrSeverity Source #
Severity: not sure what the consequences of the individual severities are
Attributes
newtype AttributeName Source #
Newtype wrapper to wrap an attribute name
Instances
Show AttributeName Source # | |
Defined in Tango.Client showsPrec :: Int -> AttributeName -> ShowS # show :: AttributeName -> String # showList :: [AttributeName] -> ShowS # |
data AttributeInfo Source #
Information for a single attribute (for spectrum and images as well, see the dimensions)
Instances
Show AttributeInfo Source # | |
Defined in Tango.Client showsPrec :: Int -> AttributeInfo -> ShowS # show :: AttributeInfo -> String # showList :: [AttributeInfo] -> ShowS # |
getConfigsForAttributes :: forall m. MonadUnliftIO m => DeviceProxy -> [AttributeName] -> m [AttributeInfo] Source #
Get information for a set of attributes (see getConfigForAttribute
for a single attribute)
getConfigForAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m AttributeInfo Source #
Get information on a single attribute (this uses getConfigsForAttributes
internally)
data TangoValue a Source #
Represents an attribute's value, with read and write part, for different data types. Fields for quality etc. are currently missing
TangoValue | |
|
Instances
Show a => Show (TangoValue a) Source # | |
Defined in Tango.Client showsPrec :: Int -> TangoValue a -> ShowS # show :: TangoValue a -> String # showList :: [TangoValue a] -> ShowS # |
Represents an image attribute's value
data TangoAttrMemorizedType Source #
Instances
More general types
Reading
readIntegralAttribute :: forall m i. (MonadUnliftIO m, Integral i, Show i) => DeviceProxy -> AttributeName -> m (TangoValue i) Source #
Read an attribute irrespective of the concrete integral type. This just uses fromIntegral
internally.
readIntegralImageAttribute :: (MonadUnliftIO m, Integral i, Show i) => DeviceProxy -> AttributeName -> m (TangoValue (Image i)) Source #
Read a spectrum image attribute irrespective of the concrete integral element type. This just uses fromIntegral
internally.
readIntegralSpectrumAttribute :: (MonadUnliftIO m, Integral i, Show i) => DeviceProxy -> AttributeName -> m (TangoValue [i]) Source #
Read a spectrum attribute irrespective of the concrete integral element type. This just uses fromIntegral
internally.
readRealAttribute :: forall m i. (MonadUnliftIO m, Fractional i, Show i) => DeviceProxy -> AttributeName -> m (TangoValue i) Source #
Read an attribute irrespective of the concrete real type. This just uses realToFrac
internally.
readRealImageAttribute :: (MonadUnliftIO m, Fractional i, Show i) => DeviceProxy -> AttributeName -> m (TangoValue (Image i)) Source #
Read a spectrum image attribute irrespective of the concrete integral element type. This just uses realToFrac
internally.
readRealSpectrumAttribute :: (MonadUnliftIO m, Fractional i, Show i) => DeviceProxy -> AttributeName -> m (TangoValue [i]) Source #
Read a spectrum attribute irrespective of the concrete real element type. This just uses realToFrac
internally.
Writing
writeIntegralAttribute :: (MonadUnliftIO m, Integral i) => DeviceProxy -> AttributeName -> i -> m () Source #
Read an attribute irrespective of the concrete integral type. This just uses fromIntegral
internally to convert from any integral type. However, we do query the attribute type beforehand, making this two calls instead of just one. If you're really concerned about performance, try to find out the real type of the attribute.
writeIntegralImageAttribute :: (MonadUnliftIO m, Integral i) => DeviceProxy -> AttributeName -> Image i -> m () Source #
Read a spectrum attribute irrespective of the concrete integral type. This just uses fromIntegral
internally to convert from any integral type. However, we do query the attribute type beforehand, making this two calls instead of just one. If you're really concerned about performance, try to find out the real type of the attribute.
writeIntegralSpectrumAttribute :: (MonadUnliftIO m, Integral i) => DeviceProxy -> AttributeName -> [i] -> m () Source #
Read a spectrum attribute irrespective of the concrete integral type. This just uses fromIntegral
internally to convert from any integral type. However, we do query the attribute type beforehand, making this two calls instead of just one. If you're really concerned about performance, try to find out the real type of the attribute.
writeRealAttribute :: (MonadUnliftIO m, Real i) => DeviceProxy -> AttributeName -> i -> m () Source #
Read an attribute irrespective of the concrete integral type. This just uses fromIntegral
internally to convert from any integral type. However, we do query the attribute type beforehand, making this two calls instead of just one. If you're really concerned about performance, try to find out the real type of the attribute.
writeRealImageAttribute :: (MonadUnliftIO m, Real i) => DeviceProxy -> AttributeName -> Image i -> m () Source #
Read a spectrum attribute irrespective of the concrete integral type. This just uses fromIntegral
internally to convert from any integral type. However, we do query the attribute type beforehand, making this two calls instead of just one. If you're really concerned about performance, try to find out the real type of the attribute.
writeRealSpectrumAttribute :: (MonadUnliftIO m, Real i) => DeviceProxy -> AttributeName -> [i] -> m () Source #
Read a spectrum attribute irrespective of the concrete real type. This just uses realToFrac
internally to convert from any integral type. However, we do query the attribute type beforehand, making this two calls instead of just one. If you're really concerned about performance, try to find out the real type of the attribute.
Specific types
Reading
readBoolAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue Bool) Source #
Read a boolean-type scalar attribute, fail hard if it's not really a bool
readBoolImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image Bool)) Source #
Read a boolean-type image attribute, fail hard if it's not really a bool
readBoolSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [Bool]) Source #
Read a boolean-type spectrum (list) attribute, fail hard if it's not really a bool
readDoubleAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue Double) Source #
Read a double-type scalar attribute, fail hard if it's not really a double
readDoubleImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image Double)) Source #
Read a double-type image attribute, fail hard if it's not really a double
readDoubleSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [Double]) Source #
Read a double-type spectrum (list) attribute, fail hard if it's not really a double
readEnumAttribute :: (MonadUnliftIO m, Enum t) => DeviceProxy -> AttributeName -> m (TangoValue t) Source #
Read an enum-type scalar attribute, fail hard if it's not really an enum (internally, enums are shorts)
readEnumImageAttribute :: (MonadUnliftIO m, Enum t) => DeviceProxy -> AttributeName -> m (TangoValue (Image t)) Source #
Read an enum-type image attribute, fail hard if it's not really an enum (internally, enums are shorts)
readEnumSpectrumAttribute :: (MonadUnliftIO m, Enum t) => DeviceProxy -> AttributeName -> m (TangoValue [t]) Source #
Read an enum-type spectrum attribute, fail hard if it's not really an enum (internally, enums are shorts)
readFloatAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue Double) Source #
Read a float-type scalar attribute, fail hard if it's not really a float
readFloatImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image Double)) Source #
Read a float-type image attribute, fail hard if it's not really a float
readFloatSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [Double]) Source #
Read a float-type spectrum (list) attribute, fail hard if it's not really a float
readLong64Attribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue Int64) Source #
Read a long64-type scalar attribute, fail hard if it's not really a long64
readLong64ImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image Int64)) Source #
Read a long64-type image attribute, fail hard if it's not really a long64
readLong64SpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [Int64]) Source #
Read a long64-type spectrum (list) attribute, fail hard if it's not really a long64
readLongAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue Int64) Source #
Read a long-type scalar attribute, fail hard if it's not really a long
readLongImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image Int64)) Source #
Read a long-type image attribute, fail hard if it's not really a long
readLongSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [Int64]) Source #
Read a long-type spectrum (list) attribute, fail hard if it's not really a long
readShortAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue Int16) Source #
Read a short-type scalar attribute, fail hard if it's not really a short
readShortImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image Int16)) Source #
Read a short-type image attribute, fail hard if it's not really a short
readShortSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [Int16]) Source #
Read a short-type spectrum (list) attribute, fail hard if it's not really a short
readStateAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue HaskellTangoDevState) Source #
Read a state-type scalar attribute, fail hard if it's not really a state
readStateImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image HaskellTangoDevState)) Source #
Read a state-type image attribute, fail hard if it's not really a state
readStateSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [HaskellTangoDevState]) Source #
Read a state-type spectrum (list) attribute, fail hard if it's not really a state type
readStringAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue Text) Source #
Read a string attribute and decode it into a text, fail hard if it's not really a string.
readStringImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image Text)) Source #
Read a string image attribute and decode it into a text
readStringSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [Text]) Source #
Read a string spectrum (array/list) attribute and decode it into a text
readULong64Attribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue Word64) Source #
Read an unsigned long64-type scalar attribute, fail hard if it's not really an unsigned long64
readULong64ImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image Word64)) Source #
Read an unsigned long64-type image attribute, fail hard if it's not really an unsigned long64
readULong64SpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [Word64]) Source #
Read an unsigned long64-type spectrum (list) attribute, fail hard if it's not really an unsigned long64
readULongAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue Word64) Source #
Read an unsigned long-type scalar attribute, fail hard if it's not really an unsigned long
readULongImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image Word64)) Source #
Read an unsigned long-type image attribute, fail hard if it's not really an unsigned long
readULongSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [Word64]) Source #
Read an unsigned long-type spectrum (list) attribute, fail hard if it's not really an unsigned long
readUShortAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue Word16) Source #
Read an unsigned short-type scalar attribute, fail hard if it's not really an unsigned short
readUShortImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue (Image Word16)) Source #
Read an unsigned short-type image attribute, fail hard if it's not really an unsigned short
readUShortSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m (TangoValue [Word16]) Source #
Read an unsigned short-type spectrum (list) attribute, fail hard if it's not really an unsigned short
Writing
writeBoolAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Bool -> m () Source #
Write a boolean scalar attribute
writeBoolImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image Bool -> m () Source #
Write a boolean image attribute
writeBoolSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [Bool] -> m () Source #
Write a boolean spectrum attribute
writeDoubleAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Double -> m () Source #
Write a double scalar attribute
writeDoubleImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image Double -> m () Source #
Write a double image attribute
writeDoubleSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [Double] -> m () Source #
Write a double spectrum attribute
writeEnumAttribute :: (MonadUnliftIO m, Enum t) => DeviceProxy -> AttributeName -> t -> m () Source #
Write an enum scalar attribute
writeEnumImageAttribute :: (MonadUnliftIO m, Enum t) => DeviceProxy -> AttributeName -> Image t -> m () Source #
Write an enum image attribute
writeEnumSpectrumAttribute :: (MonadUnliftIO m, Enum t) => DeviceProxy -> AttributeName -> [t] -> m () Source #
Write an enum spectrum attribute
writeFloatAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Double -> m () Source #
Write a float scalar attribute
writeFloatImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image Double -> m () Source #
Write a float image attribute
writeFloatSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [Double] -> m () Source #
Write a float spectrum attribute
writeLong64Attribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Int64 -> m () Source #
Write a long64 scalar attribute
writeLong64ImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image Int64 -> m () Source #
Write a long64 image attribute
writeLong64SpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [Int64] -> m () Source #
Write a long64 spectrum attribute
writeLongAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Int64 -> m () Source #
Write a long scalar attribute
writeLongImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image Int64 -> m () Source #
Write a long image attribute
writeLongSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [Int64] -> m () Source #
Write a long spectrum attribute
writeShortAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Int16 -> m () Source #
Write a short scalar attribute
writeShortImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image Int16 -> m () Source #
Write a short image attribute
writeShortSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [Int16] -> m () Source #
Write a short spectrum attribute
writeStateAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> HaskellTangoDevState -> m () Source #
Write a state scalar attribute
writeStateImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image HaskellTangoDevState -> m () Source #
Write a state image attribute
writeStateSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [HaskellTangoDevState] -> m () Source #
Write a state spectrum attribute
writeStringAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Text -> m () Source #
Write a string scalar attribute
writeStringImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image Text -> m () Source #
Write a string image attribute
writeStringSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [Text] -> m () Source #
Write a string spectrum attribute
writeULong64Attribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Word64 -> m () Source #
Write an unsigned long64 scalar attribute
writeULong64ImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image Word64 -> m () Source #
Write an unsigned long64 image attribute
writeULong64SpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [Word64] -> m () Source #
Write an unsigned long64 spectrum attribute
writeULongAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Word64 -> m () Source #
Write an unsigned long scalar attribute
writeULongImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image Word64 -> m () Source #
Write an unsigned long image attribute
writeULongSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [Word64] -> m () Source #
Write an unsigned long spectrum attribute
writeUShortAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Word16 -> m () Source #
Write an unsigned short scalar attribute
writeUShortImageAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Image Word16 -> m () Source #
Write an unsigned short image attribute
writeUShortSpectrumAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> [Word16] -> m () Source #
Write an unsigned short spectrum attribute
Commands
newtype CommandName Source #
Newtype wrapper around a command name
Instances
Show CommandName Source # | |
Defined in Tango.Client showsPrec :: Int -> CommandName -> ShowS # show :: CommandName -> String # showList :: [CommandName] -> ShowS # |
data DisplayLevel Source #
Where to display this command (in Jive, for example)
Instances
Bounded DisplayLevel Source # | |
Defined in Tango.Client | |
Enum DisplayLevel Source # | |
Defined in Tango.Client succ :: DisplayLevel -> DisplayLevel # pred :: DisplayLevel -> DisplayLevel # toEnum :: Int -> DisplayLevel # fromEnum :: DisplayLevel -> Int # enumFrom :: DisplayLevel -> [DisplayLevel] # enumFromThen :: DisplayLevel -> DisplayLevel -> [DisplayLevel] # enumFromTo :: DisplayLevel -> DisplayLevel -> [DisplayLevel] # enumFromThenTo :: DisplayLevel -> DisplayLevel -> DisplayLevel -> [DisplayLevel] # | |
Show DisplayLevel Source # | |
Defined in Tango.Client showsPrec :: Int -> DisplayLevel -> ShowS # show :: DisplayLevel -> String # showList :: [DisplayLevel] -> ShowS # | |
Eq DisplayLevel Source # | |
Defined in Tango.Client (==) :: DisplayLevel -> DisplayLevel -> Bool # (/=) :: DisplayLevel -> DisplayLevel -> Bool # |
commandInVoidOutVoid :: MonadUnliftIO m => DeviceProxy -> CommandName -> m () Source #
Execute command with no input and no output
data CommandData Source #
Input and output data for a command
Instances
Show CommandData Source # | |
Defined in Tango.Client showsPrec :: Int -> CommandData -> ShowS # show :: CommandData -> String # showList :: [CommandData] -> ShowS # |
commandInOutGeneric :: MonadUnliftIO m => DeviceProxy -> CommandName -> CommandData -> m CommandData Source #
Execute command with generic input and generic output. If you have an Enum
on hand, use commandInEnumOutGeneric
, commandInGenericOutEnum
and commandInEnumOutEnum
commandInEnumOutGeneric :: (MonadUnliftIO m, Enum t) => DeviceProxy -> CommandName -> t -> m CommandData Source #
Execute command with enum input and generic output (special case to handle arbitrary enums)
commandInGenericOutEnum :: (MonadUnliftIO m, Enum t) => DeviceProxy -> CommandName -> CommandData -> m t Source #
Execute command with generic input and enum output (special case to handle arbitrary enums)
commandInEnumOutEnum :: (MonadUnliftIO m, Enum t, Enum u) => DeviceProxy -> CommandName -> u -> m t Source #
Execute command with enum input and enum/ output (special case to handle arbitrary enums)
commandListQuery :: MonadUnliftIO m => DeviceProxy -> m [CommandInfo] Source #
Get a list of all commands for the device (see commandQuery
if you know the command name)
commandQuery :: MonadUnliftIO m => DeviceProxy -> CommandName -> m CommandInfo Source #
Get info for a single command of the device (see commandListQuery
for all commands)
data CommandInfo Source #
All information Tango has on a command
Instances
Show CommandInfo Source # | |
Defined in Tango.Client showsPrec :: Int -> CommandInfo -> ShowS # show :: CommandInfo -> String # showList :: [CommandInfo] -> ShowS # |
Properties
All data stored for a property in Tango
Property | |
|
newtype PropertyName Source #
Newtype wrapper around a property name
Instances
Show PropertyName Source # | |
Defined in Tango.Client showsPrec :: Int -> PropertyName -> ShowS # show :: PropertyName -> String # showList :: [PropertyName] -> ShowS # |
getDeviceProperties :: forall m. MonadUnliftIO m => DeviceProxy -> [PropertyName] -> m [Property] Source #
Get a list of information for the given property names
putDeviceProperties :: forall m. MonadUnliftIO m => DeviceProxy -> [(PropertyName, [Text])] -> m () Source #
Change property values for the device (here with a crude pair)
deleteDeviceProperties :: forall m. MonadUnliftIO m => DeviceProxy -> [PropertyName] -> m () Source #
Delete the given device properties
data HaskellTangoDevState Source #
List of all states that Tango knows about for device servers
Instances
Events
:: forall m. MonadUnliftIO m | |
=> DeviceProxy | |
-> AttributeName | |
-> EventType | |
-> Bool | The stateless flag = false indicates that the event subscription will only succeed when the given attribute is known and available in the Tango system. Setting stateless = true will make the subscription succeed, even if an attribute of this name was never known. The real event subscription will happen when the given attribute will be available in the Tango system. |
-> EventCallback m | |
-> m SubscribedEvent |
Subscribe to an event. See unsubscribeEvent
unsubscribeEvent :: MonadUnliftIO m => DeviceProxy -> SubscribedEvent -> m () Source #
Unsubscribe from the event, see subscribeEvent
:: MonadUnliftIO m | |
=> DeviceProxy | |
-> AttributeName | |
-> EventType | |
-> Bool | The stateless flag = false indicates that the event subscription will only succeed when the given attribute is known and available in the Tango system. Setting stateless = true will make the subscription succeed, even if an attribute of this name was never known. The real event subscription will happen when the given attribute will be available in the Tango system. |
-> EventCallback m | |
-> m () | Action to perform while we have the subscription |
-> m () |
Execute an action while being subscribed to the event
data SubscribedEvent Source #
Structure holding information on how to unsubscribe from an event again. Feed to unsubscribeEvent
Event type if you want to subscribe to events. The events are losely described in the Tango docs
ChangeEvent | It is a type of event that gets fired when the associated attribute changes its value according to its configuration specified in system specific attribute properties ( |
QualityEvent | An “alarming” (or quality) subset of change events to allow clients to monitor when attributes’ quality factors are either Tango::ATTR_WARNING or Tango::ATTR_ALARM, without receiving unneeded events relating to value changes. |
PeriodicEvent | It is a type of event that gets fired at a fixed periodic interval. |
ArchiveEvent | An event is sent if one of the archiving conditions is satisfied. Archiving conditions are defined via properties in the database. These can be a mixture of delta_change and periodic. Archive events can be send from the polling thread or can be manually pushed from the device server code ( |
UserEvent | The criteria and configuration of these user events are managed by the device server programmer who uses a specific method of one of the Tango device server class to fire the event ( |
AttrConfEvent | An event is sent if the attribute configuration is changed. |
DataReadyEvent | This event is sent when coded by the device server programmer who uses a specific method of one of the Tango device server class to fire the event ( |
InterfaceChangeEvent | This event is sent when the device interface changes. Using Tango, it is possible to dynamically addremove attributecommand to a device. This event is the way to inform client(s) that attributecommand has been addedremoved from a device. |
PipeEvent | This is the kind of event which has to be used when the user want to push data through a pipe. This kind of event is only sent by the user code by using a specific method ( |
Instances
Storable EventType Source # | |
Defined in Tango.Raw.Common | |
Bounded EventType Source # | |
Enum EventType Source # | |
Defined in Tango.Raw.Common succ :: EventType -> EventType # pred :: EventType -> EventType # fromEnum :: EventType -> Int # enumFrom :: EventType -> [EventType] # enumFromThen :: EventType -> EventType -> [EventType] # enumFromTo :: EventType -> EventType -> [EventType] # enumFromThenTo :: EventType -> EventType -> EventType -> [EventType] # | |
Show EventType Source # | |
Eq EventType Source # | |
Ord EventType Source # | |
Defined in Tango.Raw.Common |
Database proxy
type DatabaseProxy = DatabaseProxyPtr Source #
This just looks nicer because not a pointer
createDatabaseProxy :: MonadUnliftIO m => m DatabaseProxy Source #
Create a proxy for the Tango DB (not the same as a device proxy), see deleteDatabaseProxy
and withDatabaseProxy
deleteDatabaseProxy :: MonadUnliftIO m => DatabaseProxy -> m () Source #
Delete proxy for the Tango DB, see createDatabaseProxy
and withDatabaseProxy
withDatabaseProxy :: MonadUnliftIO m => (DatabaseProxy -> m a) -> m a Source #
Execute an action safely, on a database proxy, see createDatabaseProxy
and deleteDatabaseProxy
databaseSearchByDeviceName :: MonadUnliftIO m => DatabaseProxy -> Text -> m [Text] Source #
Search the database for devices with a certain name filter. Can include globs, such as sys/*
to search for all devices starting with sys
.
databaseSearchByClass :: MonadUnliftIO m => DatabaseProxy -> Text -> m [Text] Source #
Search the database for devices with a certain class
databaseSearchObjectsByName :: MonadUnliftIO m => DatabaseProxy -> Text -> m [Text] Source #
Search the database for objects with a certain name (don't know what this is)
databaseSearchObjectPropertiesByName :: MonadUnliftIO m => DatabaseProxy -> Text -> Text -> m [Text] Source #
I don't know what this is for
Various other device-related functions
lockDevice :: MonadUnliftIO m => DeviceProxy -> m () Source #
Lock the device (see withLocked
for an exception-safe version of this)
unlockDevice :: MonadUnliftIO m => DeviceProxy -> m () Source #
Unlock the device (see withLocked
for an exception-safe version of this)
getAttributeNames :: MonadUnliftIO m => DeviceProxy -> m [AttributeName] Source #
Get a list of all attributes inside the device
withLocked :: MonadUnliftIO m => DeviceProxy -> m () -> m () Source #
Execute the given action with a locked device (see lockDevice
and unlockDevice
)
setTimeout :: MonadUnliftIO m => DeviceProxy -> Milliseconds -> m () Source #
Set timeout for this device (relates to most operations: reading an attribute, executing a command)
getTimeout :: MonadUnliftIO m => DeviceProxy -> m Milliseconds Source #
Get current timeout for this device
pollCommand :: MonadUnliftIO m => DeviceProxy -> CommandName -> Milliseconds -> m () Source #
Enable polling for a command (see stopPollCommand
to stop it)
stopPollCommand :: MonadUnliftIO m => DeviceProxy -> CommandName -> m () Source #
Disable polling for a command (see pollCommand
)
pollAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> Milliseconds -> m () Source #
Enable polling for an attribute (see stopPollAttribute
to stop it)
stopPollAttribute :: MonadUnliftIO m => DeviceProxy -> AttributeName -> m () Source #
Disable polling for an attribute (see pollAttribute
)