hpio-0.9.0.5: Monads for GPIO in Haskell

Copyright(c) 2018 Quixoftic LLC
LicenseBSD3
MaintainerDrew Hess <dhess-src@quixoftic.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell2010

System.GPIO.Linux.Sysfs.Types

Contents

Description

Types used by the various Linux sysfs GPIO implementations.

Synopsis

sysfs-specific types

data SysfsEdge Source #

Linux GPIO pins that can be configured to generate inputs have an edge attribute in the sysfs GPIO filesystem. This type represents the values that the edge attribute can take.

Note that in Linux sysfs GPIO, the signal edge referred to by the edge attribute refers to the signal's logical value; i.e., it takes into account the value of the pin's active_low attribute.

This type is isomorphic to the PinInterruptMode type. See toPinInterruptMode and toSysfsEdge.

Constructors

None

Interrupts disabled

Rising

Interrupt on the (logical) signal's rising edge

Falling

Interrupt on the (logical) signal's falling edge

Both

Interrupt on any change to the signal level

Instances

Bounded SysfsEdge Source # 
Enum SysfsEdge Source # 
Eq SysfsEdge Source # 
Data SysfsEdge Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SysfsEdge -> c SysfsEdge #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SysfsEdge #

toConstr :: SysfsEdge -> Constr #

dataTypeOf :: SysfsEdge -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SysfsEdge) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SysfsEdge) #

gmapT :: (forall b. Data b => b -> b) -> SysfsEdge -> SysfsEdge #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SysfsEdge -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SysfsEdge -> r #

gmapQ :: (forall d. Data d => d -> u) -> SysfsEdge -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SysfsEdge -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SysfsEdge -> m SysfsEdge #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SysfsEdge -> m SysfsEdge #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SysfsEdge -> m SysfsEdge #

Ord SysfsEdge Source # 
Read SysfsEdge Source # 
Show SysfsEdge Source # 
Generic SysfsEdge Source # 

Associated Types

type Rep SysfsEdge :: * -> * #

Arbitrary SysfsEdge Source # 
type Rep SysfsEdge Source # 
type Rep SysfsEdge = D1 * (MetaData "SysfsEdge" "System.GPIO.Linux.Sysfs.Types" "hpio-0.9.0.5-BNWoC0QSzOQ5FCpBME6lx0" False) ((:+:) * ((:+:) * (C1 * (MetaCons "None" PrefixI False) (U1 *)) (C1 * (MetaCons "Rising" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Falling" PrefixI False) (U1 *)) (C1 * (MetaCons "Both" PrefixI False) (U1 *))))

toPinInterruptMode :: SysfsEdge -> PinInterruptMode Source #

Convert a SysfsEdge value to its equivalent PinInterruptMode value.

>>> toPinInterruptMode None
Disabled
>>> toPinInterruptMode Rising
RisingEdge
>>> toPinInterruptMode Falling
FallingEdge
>>> toPinInterruptMode Both
Level

toSysfsEdge :: PinInterruptMode -> SysfsEdge Source #

Convert a PinInterruptMode value to its equivalent SysfsEdge value.

>>> toSysfsEdge Disabled
None
>>> toSysfsEdge RisingEdge
Rising
>>> toSysfsEdge FallingEdge
Falling
>>> toSysfsEdge Level
Both

Exceptions

data SysfsException Source #

Exceptions that can be thrown by sysfs computations (in addition to standard IOError exceptions, of course).

The UnexpectedX values are truly exceptional and mean that, while the sysfs attribute for the given pin exists, the contents of the attribute do not match any expected value for that attribute, which probably means that the package is incompatible with the sysfs filesystem due to a kernel-level change.

Constructors

SysfsNotPresent

The sysfs filesystem does not exist

SysfsError

Something in the sysfs filesystem does not behave as expected (could indicate a change in sysfs behavior that the package does not expect)

SysfsPermissionDenied

The sysfs operation is not permitted due to insufficient permissions

PermissionDenied Pin

The operation on the specified pin is not permitted, either due to insufficient permissions, or because the pin's attribute cannot be modified (e.g., trying to write to a pin that's configured for input)

InvalidOperation Pin

The operation is invalid for the specified pin, or in the specified pin's current configuration

AlreadyExported Pin

The pin has already been exported

InvalidPin Pin

The specified pin does not exist

NotExported Pin

The pin has been un-exported or does not exist

UnsupportedInputMode PinInputMode Pin

The pin does not support the specified input mode

UnsupportedOutputMode PinOutputMode Pin

The pin does not support the specified output mode

NoDirectionAttribute Pin

The pin does not have a direction attribute

NoEdgeAttribute Pin

The pin does not have an edge attribute

UnexpectedDirection Pin Text

An unexpected value was read from the pin's direction attribute

UnexpectedValue Pin Text

An unexpected value was read from the pin's value attribute

UnexpectedEdge Pin Text

An unexpected value was read from the pin's edge attribute

UnexpectedActiveLow Pin Text

An unexpected value was read from the pin's active_low attribute

UnexpectedContents FilePath Text

An unexpected value was read from the specified file

InternalError Text

An internal error has occurred in the interpreter, something which should "never happen" and should be reported to the package maintainer