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

Contents

Description

GPIO in Linux via the sysfs filesystem.

See the Linux kernel documentation for the definitive description of the Linux sysfs-based GPIO API and the terminology used in this module.

Pin numbering

The sysfs GPIO implementation in this module uses the same pin numbering scheme as the sysfs GPIO filesystem. For example, Pin 13 corresponds to gpio13 in the sysfs filesystem. Note that the sysfs pin numbering scheme is almost always different than the pin numbering scheme given by the platform/hardware documentation. Consult your platform documentation for the mapping of pin numbers between the two namespaces.

Synopsis

The Linux sysfs GPIO interpreter

The SysfsGpioT monad transformer provides an instance of the MonadGpio monad type class for running GPIO computations on a Linux host via the sysfs GPIO filesystem.

The implementation abstracts back-end sysfs filesystem operations via the MonadSysfs monad type class. Primarily, this abstraction exists in order to more easily test sysfs GPIO programs on non-Linux systems, or on Linux systems which lack actual GPIO functionality. To run GPIO programs on real GPIO-capable Linux systems, you'll want to combine the SysfsGpioT transformer with the SysfsIOT monad transformer. For the straightforward case of running sysfs GPIO operations directly in IO, use the provided runSysfsGpioIO wrapper; for more complicated transformer stacks, compose the runSysfsGpioT and runSysfsIOT wrappers. (See the System.GPIO.Tutorial module for details.)

For testing purposes, you can use the SysfsMock monad (or its corresponding SysfsMockT monad transformer) as the sysfs back-end, which allows you to run (mock) GPIO programs on any system. Note that the testing monads are not exported from this module; you must import the System.GPIO.Linux.Sysfs.Mock module directly.

data SysfsGpioT m a Source #

An instance of MonadGpio which translates actions in that monad to operations on Linux's native sysfs GPIO interface.

Instances

MonadTrans SysfsGpioT Source # 

Methods

lift :: Monad m => m a -> SysfsGpioT m a #

MonadTransControl SysfsGpioT Source # 

Associated Types

type StT (SysfsGpioT :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run SysfsGpioT -> m a) -> SysfsGpioT m a #

restoreT :: Monad m => m (StT SysfsGpioT a) -> SysfsGpioT m a #

(MonadState s m, MonadWriter w m, MonadReader r m) => MonadRWS r w s (SysfsGpioT m) Source # 
MonadBaseControl b m => MonadBaseControl b (SysfsGpioT m) Source # 

Associated Types

type StM (SysfsGpioT m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (SysfsGpioT m) b -> b a) -> SysfsGpioT m a #

restoreM :: StM (SysfsGpioT m) a -> SysfsGpioT m a #

MonadBase b m => MonadBase b (SysfsGpioT m) Source # 

Methods

liftBase :: b α -> SysfsGpioT m α #

MonadWriter w m => MonadWriter w (SysfsGpioT m) Source # 

Methods

writer :: (a, w) -> SysfsGpioT m a #

tell :: w -> SysfsGpioT m () #

listen :: SysfsGpioT m a -> SysfsGpioT m (a, w) #

pass :: SysfsGpioT m (a, w -> w) -> SysfsGpioT m a #

MonadState s m => MonadState s (SysfsGpioT m) Source # 

Methods

get :: SysfsGpioT m s #

put :: s -> SysfsGpioT m () #

state :: (s -> (a, s)) -> SysfsGpioT m a #

MonadReader r m => MonadReader r (SysfsGpioT m) Source # 

Methods

ask :: SysfsGpioT m r #

local :: (r -> r) -> SysfsGpioT m a -> SysfsGpioT m a #

reader :: (r -> a) -> SysfsGpioT m a #

MonadError e m => MonadError e (SysfsGpioT m) Source # 

Methods

throwError :: e -> SysfsGpioT m a #

catchError :: SysfsGpioT m a -> (e -> SysfsGpioT m a) -> SysfsGpioT m a #

(MonadMask m, ThrowCatchSysfsM m) => MonadGpio PinDescriptor (SysfsGpioT m) Source # 
Monad m => Monad (SysfsGpioT m) Source # 

Methods

(>>=) :: SysfsGpioT m a -> (a -> SysfsGpioT m b) -> SysfsGpioT m b #

(>>) :: SysfsGpioT m a -> SysfsGpioT m b -> SysfsGpioT m b #

return :: a -> SysfsGpioT m a #

fail :: String -> SysfsGpioT m a #

Functor m => Functor (SysfsGpioT m) Source # 

Methods

fmap :: (a -> b) -> SysfsGpioT m a -> SysfsGpioT m b #

(<$) :: a -> SysfsGpioT m b -> SysfsGpioT m a #

MonadFix m => MonadFix (SysfsGpioT m) Source # 

Methods

mfix :: (a -> SysfsGpioT m a) -> SysfsGpioT m a #

Applicative m => Applicative (SysfsGpioT m) Source # 

Methods

pure :: a -> SysfsGpioT m a #

(<*>) :: SysfsGpioT m (a -> b) -> SysfsGpioT m a -> SysfsGpioT m b #

liftA2 :: (a -> b -> c) -> SysfsGpioT m a -> SysfsGpioT m b -> SysfsGpioT m c #

(*>) :: SysfsGpioT m a -> SysfsGpioT m b -> SysfsGpioT m b #

(<*) :: SysfsGpioT m a -> SysfsGpioT m b -> SysfsGpioT m a #

Alternative m => Alternative (SysfsGpioT m) Source # 

Methods

empty :: SysfsGpioT m a #

(<|>) :: SysfsGpioT m a -> SysfsGpioT m a -> SysfsGpioT m a #

some :: SysfsGpioT m a -> SysfsGpioT m [a] #

many :: SysfsGpioT m a -> SysfsGpioT m [a] #

MonadPlus m => MonadPlus (SysfsGpioT m) Source # 

Methods

mzero :: SysfsGpioT m a #

mplus :: SysfsGpioT m a -> SysfsGpioT m a -> SysfsGpioT m a #

MonadIO m => MonadIO (SysfsGpioT m) Source # 

Methods

liftIO :: IO a -> SysfsGpioT m a #

MonadThrow m => MonadThrow (SysfsGpioT m) Source # 

Methods

throwM :: Exception e => e -> SysfsGpioT m a #

MonadCatch m => MonadCatch (SysfsGpioT m) Source # 

Methods

catch :: Exception e => SysfsGpioT m a -> (e -> SysfsGpioT m a) -> SysfsGpioT m a #

MonadMask m => MonadMask (SysfsGpioT m) Source # 

Methods

mask :: ((forall a. SysfsGpioT m a -> SysfsGpioT m a) -> SysfsGpioT m b) -> SysfsGpioT m b #

uninterruptibleMask :: ((forall a. SysfsGpioT m a -> SysfsGpioT m a) -> SysfsGpioT m b) -> SysfsGpioT m b #

MonadLogger m => MonadLogger (SysfsGpioT m) Source # 

Methods

monadLoggerLog :: ToLogStr msg => Loc -> LogSource -> LogLevel -> msg -> SysfsGpioT m () #

MonadLoggerIO m => MonadLoggerIO (SysfsGpioT m) Source # 

Methods

askLoggerIO :: SysfsGpioT m (Loc -> LogSource -> LogLevel -> LogStr -> IO ()) #

MonadCont m => MonadCont (SysfsGpioT m) Source # 

Methods

callCC :: ((a -> SysfsGpioT m b) -> SysfsGpioT m a) -> SysfsGpioT m a #

type StT SysfsGpioT a Source # 
type StT SysfsGpioT a = a
type StM (SysfsGpioT m) a Source # 

type SysfsGpioIO = SysfsGpioT (SysfsIOT IO) Source #

A specialization of SysfsGpioT which runs GPIO computations in IO via sysfs.

runSysfsGpioIO :: SysfsGpioIO a -> IO a Source #

Run GPIO computations in IO via sysfs.

newtype PinDescriptor Source #

The sysfs pin handle type. Currently it's just a newtype wrapper around a Pin. The constructor is exported for convenience, but note that the implementation may change in future versions of the package.

Constructors

PinDescriptor 

Fields

Instances

Eq PinDescriptor Source # 
Ord PinDescriptor Source # 
Show PinDescriptor Source # 
(MonadMask m, ThrowCatchSysfsM m) => MonadGpio PinDescriptor (SysfsGpioT m) Source # 

The Linux sysfs monad

class Monad m => MonadSysfs m where Source #

A type class for monads which implement (or mock) low-level Linux sysfs GPIO operations.

Methods

doesDirectoryExist :: FilePath -> m Bool Source #

Equivalent to doesDirectoryExist.

doesFileExist :: FilePath -> m Bool Source #

Equivalent to doesFileExist.

getDirectoryContents :: FilePath -> m [FilePath] Source #

Equivalent to getDirectoryContents.

readFile :: FilePath -> m ByteString Source #

Equivalent to readFile.

writeFile :: FilePath -> ByteString -> m () Source #

Equivalent to writeFile.

unlockedWriteFile :: FilePath -> ByteString -> m () Source #

sysfs control files which are global shared resources may be written simultaneously by multiple threads. This is fine -- sysfs can handle this -- but Haskell's writeFile cannot, as it locks the file and prevents multiple writers. We don't want this behavior, so we use low-level operations to get around it.

pollFile :: FilePath -> Int -> m CInt Source #

Poll a sysfs file for reading, as in POSIX.1-2001 poll(2).

Note that the implementation of this action is only guaranteed to work for sysfs files, which have a peculiar way of signaling readiness for reads. Do not use it for any other purpose.

doesDirectoryExist :: (MonadTrans t, MonadSysfs m', t m' ~ m) => FilePath -> m Bool Source #

Equivalent to doesDirectoryExist.

doesFileExist :: (MonadTrans t, MonadSysfs m', t m' ~ m) => FilePath -> m Bool Source #

Equivalent to doesFileExist.

getDirectoryContents :: (MonadTrans t, MonadSysfs m', t m' ~ m) => FilePath -> m [FilePath] Source #

Equivalent to getDirectoryContents.

readFile :: (MonadTrans t, MonadSysfs m', t m' ~ m) => FilePath -> m ByteString Source #

Equivalent to readFile.

writeFile :: (MonadTrans t, MonadSysfs m', t m' ~ m) => FilePath -> ByteString -> m () Source #

Equivalent to writeFile.

unlockedWriteFile :: (MonadTrans t, MonadSysfs m', t m' ~ m) => FilePath -> ByteString -> m () Source #

sysfs control files which are global shared resources may be written simultaneously by multiple threads. This is fine -- sysfs can handle this -- but Haskell's writeFile cannot, as it locks the file and prevents multiple writers. We don't want this behavior, so we use low-level operations to get around it.

pollFile :: (MonadTrans t, MonadSysfs m', t m' ~ m) => FilePath -> Int -> m CInt Source #

Poll a sysfs file for reading, as in POSIX.1-2001 poll(2).

Note that the implementation of this action is only guaranteed to work for sysfs files, which have a peculiar way of signaling readiness for reads. Do not use it for any other purpose.

Instances

MonadSysfs m => MonadSysfs (MaybeT m) Source # 
MonadSysfs m => MonadSysfs (CatchT m) Source # 
MonadSysfs m => MonadSysfs (ListT m) Source # 
MonadSysfs m => MonadSysfs (NoLoggingT m) Source # 
MonadSysfs m => MonadSysfs (LoggingT m) Source # 
(MonadIO m, MonadThrow m) => MonadSysfs (SysfsIOT m) Source # 
MockM m => MonadSysfs (SysfsMockT m) Source # 
(MonadSysfs m, Monoid w) => MonadSysfs (WriterT w m) Source # 
(MonadSysfs m, Monoid w) => MonadSysfs (WriterT w m) Source # 
MonadSysfs m => MonadSysfs (StateT s m) Source # 
MonadSysfs m => MonadSysfs (StateT s m) Source # 
MonadSysfs m => MonadSysfs (ExceptT e m) Source # 
MonadSysfs m => MonadSysfs (IdentityT * m) Source # 
MonadSysfs m => MonadSysfs (ReaderT * r m) Source # 
MonadSysfs m => MonadSysfs (ContT * r m) Source # 
(MonadSysfs m, Monoid w) => MonadSysfs (RWST r w s m) Source # 
(MonadSysfs m, Monoid w) => MonadSysfs (RWST r w s m) Source # 

newtype SysfsIOT m a Source #

An instance of MonadSysfs which runs MonadSysfs operations in IO. This instance must be run on an actual Linux sysfs GPIO filesystem and will fail in any other environment.

Interactions with threads

Some parts of this implementation use the Haskell C FFI, and may block on C I/O operations. (Specifically, pollFile will block in the C FFI until its event is triggered.) When using this implementation with GHC, you should compile your program with the -threaded option, so that threads performing these blocking operations do not block other Haskell threads in the system.

Note that the C FFI bits in this implementation are marked as interruptible, so that, on versions of GHC later than 7.8.1, functions such as throwTo will work properly when targeting a Haskell thread that uses this implementation.

(On Haskell implementations other than GHC, the threading implications are unknown; see the implementation's notes on how its threading system interacts with the C FFI.)

Constructors

SysfsIOT 

Fields

Instances

MonadTrans SysfsIOT Source # 

Methods

lift :: Monad m => m a -> SysfsIOT m a #

MonadTransControl SysfsIOT Source # 

Associated Types

type StT (SysfsIOT :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run SysfsIOT -> m a) -> SysfsIOT m a #

restoreT :: Monad m => m (StT SysfsIOT a) -> SysfsIOT m a #

(MonadState s m, MonadWriter w m, MonadReader r m) => MonadRWS r w s (SysfsIOT m) Source # 
MonadBaseControl b m => MonadBaseControl b (SysfsIOT m) Source # 

Associated Types

type StM (SysfsIOT m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (SysfsIOT m) b -> b a) -> SysfsIOT m a #

restoreM :: StM (SysfsIOT m) a -> SysfsIOT m a #

MonadBase b m => MonadBase b (SysfsIOT m) Source # 

Methods

liftBase :: b α -> SysfsIOT m α #

MonadWriter w m => MonadWriter w (SysfsIOT m) Source # 

Methods

writer :: (a, w) -> SysfsIOT m a #

tell :: w -> SysfsIOT m () #

listen :: SysfsIOT m a -> SysfsIOT m (a, w) #

pass :: SysfsIOT m (a, w -> w) -> SysfsIOT m a #

MonadState s m => MonadState s (SysfsIOT m) Source # 

Methods

get :: SysfsIOT m s #

put :: s -> SysfsIOT m () #

state :: (s -> (a, s)) -> SysfsIOT m a #

MonadReader r m => MonadReader r (SysfsIOT m) Source # 

Methods

ask :: SysfsIOT m r #

local :: (r -> r) -> SysfsIOT m a -> SysfsIOT m a #

reader :: (r -> a) -> SysfsIOT m a #

MonadError e m => MonadError e (SysfsIOT m) Source # 

Methods

throwError :: e -> SysfsIOT m a #

catchError :: SysfsIOT m a -> (e -> SysfsIOT m a) -> SysfsIOT m a #

Monad m => Monad (SysfsIOT m) Source # 

Methods

(>>=) :: SysfsIOT m a -> (a -> SysfsIOT m b) -> SysfsIOT m b #

(>>) :: SysfsIOT m a -> SysfsIOT m b -> SysfsIOT m b #

return :: a -> SysfsIOT m a #

fail :: String -> SysfsIOT m a #

Functor m => Functor (SysfsIOT m) Source # 

Methods

fmap :: (a -> b) -> SysfsIOT m a -> SysfsIOT m b #

(<$) :: a -> SysfsIOT m b -> SysfsIOT m a #

MonadFix m => MonadFix (SysfsIOT m) Source # 

Methods

mfix :: (a -> SysfsIOT m a) -> SysfsIOT m a #

Applicative m => Applicative (SysfsIOT m) Source # 

Methods

pure :: a -> SysfsIOT m a #

(<*>) :: SysfsIOT m (a -> b) -> SysfsIOT m a -> SysfsIOT m b #

liftA2 :: (a -> b -> c) -> SysfsIOT m a -> SysfsIOT m b -> SysfsIOT m c #

(*>) :: SysfsIOT m a -> SysfsIOT m b -> SysfsIOT m b #

(<*) :: SysfsIOT m a -> SysfsIOT m b -> SysfsIOT m a #

Alternative m => Alternative (SysfsIOT m) Source # 

Methods

empty :: SysfsIOT m a #

(<|>) :: SysfsIOT m a -> SysfsIOT m a -> SysfsIOT m a #

some :: SysfsIOT m a -> SysfsIOT m [a] #

many :: SysfsIOT m a -> SysfsIOT m [a] #

MonadPlus m => MonadPlus (SysfsIOT m) Source # 

Methods

mzero :: SysfsIOT m a #

mplus :: SysfsIOT m a -> SysfsIOT m a -> SysfsIOT m a #

MonadIO m => MonadIO (SysfsIOT m) Source # 

Methods

liftIO :: IO a -> SysfsIOT m a #

MonadThrow m => MonadThrow (SysfsIOT m) Source # 

Methods

throwM :: Exception e => e -> SysfsIOT m a #

MonadCatch m => MonadCatch (SysfsIOT m) Source # 

Methods

catch :: Exception e => SysfsIOT m a -> (e -> SysfsIOT m a) -> SysfsIOT m a #

MonadMask m => MonadMask (SysfsIOT m) Source # 

Methods

mask :: ((forall a. SysfsIOT m a -> SysfsIOT m a) -> SysfsIOT m b) -> SysfsIOT m b #

uninterruptibleMask :: ((forall a. SysfsIOT m a -> SysfsIOT m a) -> SysfsIOT m b) -> SysfsIOT m b #

MonadLogger m => MonadLogger (SysfsIOT m) Source # 

Methods

monadLoggerLog :: ToLogStr msg => Loc -> LogSource -> LogLevel -> msg -> SysfsIOT m () #

MonadLoggerIO m => MonadLoggerIO (SysfsIOT m) Source # 

Methods

askLoggerIO :: SysfsIOT m (Loc -> LogSource -> LogLevel -> LogStr -> IO ()) #

MonadCont m => MonadCont (SysfsIOT m) Source # 

Methods

callCC :: ((a -> SysfsIOT m b) -> SysfsIOT m a) -> SysfsIOT m a #

(MonadIO m, MonadThrow m) => MonadSysfs (SysfsIOT m) Source # 
type StT SysfsIOT a Source # 
type StT SysfsIOT a = a
type StM (SysfsIOT m) a Source # 
type StM (SysfsIOT m) a = ComposeSt SysfsIOT m a

Low-level sysfs GPIO actions

A slightly more low-level API is also available if you want to write directly to the Linux sysfs GPIO filesystem, or do something that the MonadGpio portable GPIO interface doesn't allow you to express.

sysfsIsPresent :: MonadSysfs m => m Bool Source #

Test whether the sysfs GPIO filesystem is available.

availablePins :: ThrowCatchSysfsM m => m [Pin] Source #

Return a list of all pins that are exposed via the sysfs GPIO filesystem. Note that the returned list may omit some pins that are available on the host but which, for various reasons, are not exposed via the sysfs GPIO filesystem.

pinIsExported :: MonadSysfs m => Pin -> m Bool Source #

Test whether the pin is already exported.

exportPin :: CatchSysfsM m => Pin -> m () Source #

Export the given pin.

Note that, if the pin is already exported, this is not an error; in this situation, the pin remains exported and its state unchanged.

exportPinChecked :: CatchSysfsM m => Pin -> m () Source #

Export the given pin.

Note that, unlike exportPin, it's an error to call this action to export a pin that's already been exported. This is the standard Linux sysfs GPIO behavior.

unexportPin :: CatchSysfsM m => Pin -> m () Source #

Unexport the given pin.

Note that, if the pin is already unexported or cannot be unexported, this is not an error. In this situation, the pin remains exported and its state unchanged.

unexportPinChecked :: CatchSysfsM m => Pin -> m () Source #

Unexport the given pin.

Note that, unlike unexportPin, it is an error to call this action if the pin is not currently exported. This is the standard Linux sysfs GPIO behavior.

pinHasDirection :: ThrowSysfsM m => Pin -> m Bool Source #

Test whether the pin's direction can be set via the sysfs GPIO filesystem. (Some pins have a hard-wired direction, in which case their direction must be determined by some other mechanism, as the direction attribute does not exist for such pins.)

readPinDirection :: ThrowCatchSysfsM m => Pin -> m PinDirection Source #

Read the pin's direction.

It is an error to call this action if the pin has no direction attribute.

writePinDirection :: CatchSysfsM m => Pin -> PinDirection -> m () Source #

Set the pin's direction.

It is an error to call this action if the pin has no direction attribute.

Note that, in Linux sysfs GPIO, changing a pin's direction to out will also set its physical signal level to low.

NB: in Linux sysfs, if an input pin is cofigured for edge- or level-triggered reads, it's an error to set its direction to out. However, this action will handle that case gracefully by setting the pin's edge attribute to none before setting the pin's direction to out.

writePinDirectionWithValue :: CatchSysfsM m => Pin -> PinValue -> m () Source #

Pins whose direction can be set may be configured for output by writing a PinValue to their direction attribute, such that the given value will be driven on the pin as soon as it's configured for output. This enables glitch-free output configuration, assuming the pin is currently configured for input, or some kind of tri-stated or floating high-impedance mode.

It is an error to call this action if the pin has no direction attribute.

NB: for some unfathomable reason, writing high or low to a pin's direction attribute sets its physical signal level; i.e., it ignores the value of the pin's active_low attribute. Contrast this behavior with the behavior of writing to the pin's value attribute, which respects the value of the pin's active_low attribute and sets the pin's logical signal level.

Rather than slavishly following the Linux sysfs GPIO spec, we choose to be consistent by taking into account the pin's active level when writing the direction attribute. In other words, the PinValue argument to this action is the logical signal level that will be set on the pin. If you're using this action to program directly to the Linux sysfs GPIO interface and expecting things to behave as they do with raw sysfs GPIO operations, keep this in mind!

readPinValue :: ThrowCatchSysfsM m => Pin -> m PinValue Source #

Read the pin's signal level.

Note that this action never blocks, regardless of the pin's edge attribute setting.

pollPinValue :: ThrowCatchSysfsM m => Pin -> m PinValue Source #

A blocking version of readPinValue. The current thread will block until an event occurs on the pin as specified by the pin's current edge attribute setting.

If the pin has no edge attribute, then this action's behavior is undefined. (Most likely, it will block indefinitely.)

pollPinValueTimeout :: ThrowCatchSysfsM m => Pin -> Int -> m (Maybe PinValue) Source #

Same as pollPinValue, except that a timeout value, specified in microseconds, is provided. If no event occurs before the timeout expires, this action returns Nothing; otherwise, it returns the pin's value wrapped in a Just.

If the timeout value is negative, this action behaves just like pollPinValue.

When specifying a timeout value, be careful not to exceed maxBound.

If the pin has no edge attribute, then this action's behavior is undefined. (Most likely, it will time out after the specified delay and return Nothing.)

NB: the curent implementation of this action limits the timeout precision to 1 millisecond, rather than 1 microsecond as the timeout parameter implies.

writePinValue :: CatchSysfsM m => Pin -> PinValue -> m () Source #

Set the pin's signal level.

It is an error to call this action if the pin is configured as an input pin.

pinHasEdge :: ThrowSysfsM m => Pin -> m Bool Source #

Test whether the pin has an edge attribute, i.e., whether it can be configured for edge- or level-triggered interrupts.

readPinEdge :: ThrowCatchSysfsM m => Pin -> m SysfsEdge Source #

Read the pin's edge attribute.

It is an error to call this action when the pin has no edge attribute.

writePinEdge :: CatchSysfsM m => Pin -> SysfsEdge -> m () Source #

Write the pin's edge attribute.

It is an error to call this action when the pin has no edge attribute, or when the pin is configured for output.

readPinActiveLow :: ThrowCatchSysfsM m => Pin -> m Bool Source #

Read the pin's active_low attribute.

writePinActiveLow :: CatchSysfsM m => Pin -> Bool -> m () Source #

Write the pin's active_low attribute.

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.4-KvjlItLndKJHsjaZuulG4w" 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

sysfs-specific 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