hs-tango-1.0.0: Bindings to the Tango Controls system
Safe HaskellSafe-Inferred
LanguageHaskell2010

Tango.Client

Description

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

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

data TangoUrl Source #

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

Constructors

Milliseconds Int 

Instances

Instances details
Show Milliseconds Source # 
Instance details

Defined in Tango.Client

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

Constructors

TangoException [DevFailed Text] 

data ErrSeverity Source #

How severe is the error (used in the Tango error types)

Constructors

Warn 
Err 
Panic 

data DevFailed a Source #

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)

Constructors

DevFailed !a !a !a !ErrSeverity 

Instances

Instances details
Foldable DevFailed Source # 
Instance details

Defined in Tango.Raw.Common

Methods

fold :: Monoid m => DevFailed m -> m #

foldMap :: Monoid m => (a -> m) -> DevFailed a -> m #

foldMap' :: Monoid m => (a -> m) -> DevFailed a -> m #

foldr :: (a -> b -> b) -> b -> DevFailed a -> b #

foldr' :: (a -> b -> b) -> b -> DevFailed a -> b #

foldl :: (b -> a -> b) -> b -> DevFailed a -> b #

foldl' :: (b -> a -> b) -> b -> DevFailed a -> b #

foldr1 :: (a -> a -> a) -> DevFailed a -> a #

foldl1 :: (a -> a -> a) -> DevFailed a -> a #

toList :: DevFailed a -> [a] #

null :: DevFailed a -> Bool #

length :: DevFailed a -> Int #

elem :: Eq a => a -> DevFailed a -> Bool #

maximum :: Ord a => DevFailed a -> a #

minimum :: Ord a => DevFailed a -> a #

sum :: Num a => DevFailed a -> a #

product :: Num a => DevFailed a -> a #

Traversable DevFailed Source # 
Instance details

Defined in Tango.Raw.Common

Methods

traverse :: Applicative f => (a -> f b) -> DevFailed a -> f (DevFailed b) #

sequenceA :: Applicative f => DevFailed (f a) -> f (DevFailed a) #

mapM :: Monad m => (a -> m b) -> DevFailed a -> m (DevFailed b) #

sequence :: Monad m => DevFailed (m a) -> m (DevFailed a) #

Functor DevFailed Source # 
Instance details

Defined in Tango.Raw.Common

Methods

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

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

Generic (DevFailed a) Source # 
Instance details

Defined in Tango.Raw.Common

Associated Types

type Rep (DevFailed a) :: Type -> Type #

Methods

from :: DevFailed a -> Rep (DevFailed a) x #

to :: Rep (DevFailed a) x -> DevFailed a #

Show a => Show (DevFailed a) Source # 
Instance details

Defined in Tango.Raw.Common

Storable a => GStorable (DevFailed a) Source # 
Instance details

Defined in Tango.Raw.Common

Methods

gsizeOf :: DevFailed a -> Int #

galignment :: DevFailed a -> Int #

gpeekByteOff :: Ptr b -> Int -> IO (DevFailed a) #

gpokeByteOff :: Ptr b -> Int -> DevFailed a -> IO () #

type Rep (DevFailed a) Source # 
Instance details

Defined in Tango.Raw.Common

type Rep (DevFailed a) = D1 ('MetaData "DevFailed" "Tango.Raw.Common" "hs-tango-1.0.0-inplace" 'False) (C1 ('MetaCons "DevFailed" 'PrefixI 'True) ((S1 ('MetaSel ('Just "devFailedDesc") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "devFailedReason") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)) :*: (S1 ('MetaSel ('Just "devFailedOrigin") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "devFailedSeverity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ErrSeverity))))

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

Constructors

AttributeName Text 

Instances

Instances details
Show AttributeName Source # 
Instance details

Defined in Tango.Client

data AttributeInfo Source #

Information for a single attribute (for spectrum and images as well, see the dimensions)

Instances

Instances details
Show AttributeInfo Source # 
Instance details

Defined in Tango.Client

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

Constructors

TangoValue 

Fields

Instances

Instances details
Show a => Show (TangoValue a) Source # 
Instance details

Defined in Tango.Client

data Image a Source #

Represents an image attribute's value

Constructors

Image 

Fields

Instances

Instances details
Functor Image Source # 
Instance details

Defined in Tango.Client

Methods

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

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

Show a => Show (Image a) Source # 
Instance details

Defined in Tango.Client

Methods

showsPrec :: Int -> Image a -> ShowS #

show :: Image a -> String #

showList :: [Image a] -> ShowS #

data TangoAttrMemorizedType Source #

Instances

Instances details
Storable TangoAttrMemorizedType Source # 
Instance details

Defined in Tango.Raw.Common

Bounded TangoAttrMemorizedType Source # 
Instance details

Defined in Tango.Raw.Common

Enum TangoAttrMemorizedType Source # 
Instance details

Defined in Tango.Raw.Common

Show TangoAttrMemorizedType Source # 
Instance details

Defined in Tango.Raw.Common

Eq TangoAttrMemorizedType Source # 
Instance details

Defined in Tango.Raw.Common

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

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

Constructors

CommandName Text 

Instances

Instances details
Show CommandName Source # 
Instance details

Defined in Tango.Client

commandInVoidOutVoid :: MonadUnliftIO m => DeviceProxy -> CommandName -> m () Source #

Execute command with no input and no output

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)

Properties

data Property Source #

All data stored for a property in Tango

Instances

Instances details
Show Property Source # 
Instance details

Defined in Tango.Client

newtype PropertyName Source #

Newtype wrapper around a property name

Constructors

PropertyName Text 

Instances

Instances details
Show PropertyName Source # 
Instance details

Defined in Tango.Client

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

Instances details
Storable HaskellTangoDevState Source # 
Instance details

Defined in Tango.Raw.Common

Bounded HaskellTangoDevState Source # 
Instance details

Defined in Tango.Raw.Common

Enum HaskellTangoDevState Source # 
Instance details

Defined in Tango.Raw.Common

Show HaskellTangoDevState Source # 
Instance details

Defined in Tango.Raw.Common

Eq HaskellTangoDevState Source # 
Instance details

Defined in Tango.Raw.Common

Events

subscribeEvent Source #

Arguments

:: 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

withSubscribedEvent Source #

Arguments

:: 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

data EventType Source #

Event type if you want to subscribe to events. The events are losely described in the Tango docs

Constructors

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 (abs_change and rel_change).

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 (DeviceImpl::push_archive_event()).

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 (DeviceImpl::push_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 (DeviceImpl::push_data_ready_event()). The rule of this event is to inform a client that it is now possible to read an attribute. This could be useful in case of attribute with many data.

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 (DeviceImpl::push_pipe_event()).

Instances

Instances details
Storable EventType Source # 
Instance details

Defined in Tango.Raw.Common

Bounded EventType Source # 
Instance details

Defined in Tango.Raw.Common

Enum EventType Source # 
Instance details

Defined in Tango.Raw.Common

Show EventType Source # 
Instance details

Defined in Tango.Raw.Common

Eq EventType Source # 
Instance details

Defined in Tango.Raw.Common

Ord EventType Source # 
Instance details

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)