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

Tango.Raw.Common

Description

 
Synopsis

Documentation

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

data HaskellTangoDevEncoded Source #

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

data ErrSeverity Source #

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

Constructors

Warn 
Err 
Panic 

data HaskellDbData Source #

Instances

Instances details
Generic HaskellDbData Source # 
Instance details

Defined in Tango.Raw.Common

Associated Types

type Rep HaskellDbData :: Type -> Type #

Show HaskellDbData Source # 
Instance details

Defined in Tango.Raw.Common

GStorable HaskellDbData Source # 
Instance details

Defined in Tango.Raw.Common

type Rep HaskellDbData Source # 
Instance details

Defined in Tango.Raw.Common

type Rep HaskellDbData = D1 ('MetaData "HaskellDbData" "Tango.Raw.Common" "hs-tango-1.0.0-inplace" 'False) (C1 ('MetaCons "HaskellDbData" 'PrefixI 'True) (S1 ('MetaSel ('Just "dbDataLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: S1 ('MetaSel ('Just "dbDataSequence") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ptr HaskellDbDatum))))

data HaskellAttributeInfoList Source #

data HaskellAttributeDataList Source #

data HaskellAttributeInfo Source #

Instances

Instances details
Generic HaskellAttributeInfo Source # 
Instance details

Defined in Tango.Raw.Common

Associated Types

type Rep HaskellAttributeInfo :: Type -> Type #

Show HaskellAttributeInfo Source # 
Instance details

Defined in Tango.Raw.Common

GStorable HaskellAttributeInfo Source # 
Instance details

Defined in Tango.Raw.Common

type Rep HaskellAttributeInfo Source # 
Instance details

Defined in Tango.Raw.Common

type Rep HaskellAttributeInfo = D1 ('MetaData "HaskellAttributeInfo" "Tango.Raw.Common" "hs-tango-1.0.0-inplace" 'False) (C1 ('MetaCons "HaskellAttributeInfo" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "attributeInfoName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CString) :*: S1 ('MetaSel ('Just "attributeInfoWritable") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HaskellAttrWriteType)) :*: (S1 ('MetaSel ('Just "attributeInfoDataFormat") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HaskellDataFormat) :*: (S1 ('MetaSel ('Just "attributeInfoDataType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HaskellTangoDataType) :*: S1 ('MetaSel ('Just "attributeInfoMaxDimX") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int32)))) :*: ((S1 ('MetaSel ('Just "attributeInfoMaxDimY") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int32) :*: (S1 ('MetaSel ('Just "attributeInfoDescription") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CString) :*: S1 ('MetaSel ('Just "attributeInfoLabel") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CString))) :*: (S1 ('MetaSel ('Just "attributeInfoUnit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CString) :*: (S1 ('MetaSel ('Just "attributeInfoStandardUnit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CString) :*: S1 ('MetaSel ('Just "attributeInfoDisplayUnit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CString))))) :*: (((S1 ('MetaSel ('Just "attributeInfoFormat") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CString) :*: S1 ('MetaSel ('Just "attributeInfoMinValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CString)) :*: (S1 ('MetaSel ('Just "attributeInfoMaxValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CString) :*: (S1 ('MetaSel ('Just "attributeInfoMinAlarm") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CString) :*: S1 ('MetaSel ('Just "attributeInfoMaxAlarm") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CString)))) :*: ((S1 ('MetaSel ('Just "attributeInfoWritableAttrName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CString) :*: (S1 ('MetaSel ('Just "attributeInfoDispLevel") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HaskellDispLevel) :*: S1 ('MetaSel ('Just "attributeInfoEnumLabels") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ptr CString)))) :*: (S1 ('MetaSel ('Just "attributeInfoEnumLabelsCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word16) :*: (S1 ('MetaSel ('Just "attributeInfoRootAttrName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CString) :*: S1 ('MetaSel ('Just "attributeInfoMemorized") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TangoAttrMemorizedType)))))))

data HaskellTangoVarArray a Source #

Instances

Instances details
Generic (HaskellTangoVarArray a) Source # 
Instance details

Defined in Tango.Raw.Common

Associated Types

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

Show (HaskellTangoVarArray a) Source # 
Instance details

Defined in Tango.Raw.Common

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

Defined in Tango.Raw.Common

type Rep (HaskellTangoVarArray a) Source # 
Instance details

Defined in Tango.Raw.Common

type Rep (HaskellTangoVarArray a) = D1 ('MetaData "HaskellTangoVarArray" "Tango.Raw.Common" "hs-tango-1.0.0-inplace" 'False) (C1 ('MetaCons "HaskellTangoVarArray" 'PrefixI 'True) (S1 ('MetaSel ('Just "varArrayLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: S1 ('MetaSel ('Just "varArrayValues") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ptr a))))

data Timeval Source #

Constructors

Timeval 

Fields

Instances

Instances details
Storable Timeval Source # 
Instance details

Defined in Tango.Raw.Common

Show Timeval Source # 
Instance details

Defined in Tango.Raw.Common

data HaskellErrorStack Source #

Instances

Instances details
Generic HaskellErrorStack Source # 
Instance details

Defined in Tango.Raw.Common

Associated Types

type Rep HaskellErrorStack :: Type -> Type #

GStorable HaskellErrorStack Source # 
Instance details

Defined in Tango.Raw.Common

type Rep HaskellErrorStack Source # 
Instance details

Defined in Tango.Raw.Common

type Rep HaskellErrorStack = D1 ('MetaData "HaskellErrorStack" "Tango.Raw.Common" "hs-tango-1.0.0-inplace" 'False) (C1 ('MetaCons "HaskellErrorStack" 'PrefixI 'True) (S1 ('MetaSel ('Just "errorStackLength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "errorStackSequence") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ptr (DevFailed CString)))))

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 

Fields

  • devFailedDesc :: !a

    Failure description; this will usually be the actual error message you're interested in and will be human-readable

  • devFailedReason :: !a

    Failure reason; this is usually an error code string, like API_AttrNotFound

  • devFailedOrigin :: !a

    Failure origin: this is usually the C++ function that caused the error

  • devFailedSeverity :: !ErrSeverity

    Severity: not sure what the consequences of the individual severities are

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

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

data HaskellTangoDataType Source #

Haskell mapping for the C type TangoDataType Beware: this is encoded positionally!

Instances

Instances details
Storable HaskellTangoDataType Source # 
Instance details

Defined in Tango.Raw.Common

Bounded HaskellTangoDataType Source # 
Instance details

Defined in Tango.Raw.Common

Enum HaskellTangoDataType Source # 
Instance details

Defined in Tango.Raw.Common

Show HaskellTangoDataType Source # 
Instance details

Defined in Tango.Raw.Common

Eq HaskellTangoDataType Source # 
Instance details

Defined in Tango.Raw.Common

Ord HaskellTangoDataType Source # 
Instance details

Defined in Tango.Raw.Common

data HaskellTangoCommandData Source #

data HaskellCommandInfoList Source #

createEventCallbackWrapper :: EventCallback -> IO (FunPtr EventCallback) Source #

tango_create_event_callback :: FunPtr EventCallback -> IO (Ptr ()) Source #