Copyright | (c) 2017 Quixoftic LLC |
---|---|
License | BSD3 |
Maintainer | Drew Hess <dhess-src@quixoftic.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe |
Language | Haskell2010 |
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.
- data SysfsGpioT m a
- runSysfsGpioT :: SysfsGpioT m a -> m a
- type SysfsGpioIO = SysfsGpioT (SysfsIOT IO)
- runSysfsGpioIO :: SysfsGpioIO a -> IO a
- newtype PinDescriptor = PinDescriptor {}
- class Monad m => MonadSysfs m where
- newtype SysfsIOT m a = SysfsIOT {
- runSysfsIOT :: m a
- sysfsIsPresent :: MonadSysfs m => m Bool
- availablePins :: ThrowCatchSysfsM m => m [Pin]
- pinIsExported :: MonadSysfs m => Pin -> m Bool
- exportPin :: CatchSysfsM m => Pin -> m ()
- exportPinChecked :: CatchSysfsM m => Pin -> m ()
- unexportPin :: CatchSysfsM m => Pin -> m ()
- unexportPinChecked :: CatchSysfsM m => Pin -> m ()
- pinHasDirection :: ThrowSysfsM m => Pin -> m Bool
- readPinDirection :: ThrowCatchSysfsM m => Pin -> m PinDirection
- writePinDirection :: CatchSysfsM m => Pin -> PinDirection -> m ()
- writePinDirectionWithValue :: CatchSysfsM m => Pin -> PinValue -> m ()
- readPinValue :: ThrowCatchSysfsM m => Pin -> m PinValue
- pollPinValue :: ThrowCatchSysfsM m => Pin -> m PinValue
- pollPinValueTimeout :: ThrowCatchSysfsM m => Pin -> Int -> m (Maybe PinValue)
- writePinValue :: CatchSysfsM m => Pin -> PinValue -> m ()
- pinHasEdge :: ThrowSysfsM m => Pin -> m Bool
- readPinEdge :: ThrowCatchSysfsM m => Pin -> m SysfsEdge
- writePinEdge :: CatchSysfsM m => Pin -> SysfsEdge -> m ()
- readPinActiveLow :: ThrowCatchSysfsM m => Pin -> m Bool
- writePinActiveLow :: CatchSysfsM m => Pin -> Bool -> m ()
- data SysfsEdge
- toPinInterruptMode :: SysfsEdge -> PinInterruptMode
- toSysfsEdge :: PinInterruptMode -> SysfsEdge
- data SysfsException
- = SysfsNotPresent
- | SysfsError
- | SysfsPermissionDenied
- | PermissionDenied Pin
- | InvalidOperation Pin
- | AlreadyExported Pin
- | InvalidPin Pin
- | NotExported Pin
- | UnsupportedInputMode PinInputMode Pin
- | UnsupportedOutputMode PinOutputMode Pin
- | NoDirectionAttribute Pin
- | NoEdgeAttribute Pin
- | UnexpectedDirection Pin Text
- | UnexpectedValue Pin Text
- | UnexpectedEdge Pin Text
- | UnexpectedActiveLow Pin Text
- | UnexpectedContents FilePath Text
- | InternalError Text
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.
runSysfsGpioT :: SysfsGpioT m a -> 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.
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.
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.
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 # | |
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.)
SysfsIOT | |
|
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
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
.
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.
SysfsNotPresent | The |
SysfsError | Something in the |
SysfsPermissionDenied | The |
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 |
NoEdgeAttribute Pin | The pin does not have an |
UnexpectedDirection Pin Text | An unexpected value was read from the pin's |
UnexpectedValue Pin Text | An unexpected value was read from the pin's |
UnexpectedEdge Pin Text | An unexpected value was read from the pin's |
UnexpectedActiveLow Pin Text | An unexpected value was read from the pin's |
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 |