module System.GPIO.Monad
(
Pin(..)
, pinNumber
, PinInputMode(..)
, PinOutputMode(..)
, PinCapabilities(..)
, PinDirection(..)
, PinActiveLevel(..)
, PinValue(..)
, PinInterruptMode(..)
, MonadGpio(..)
, withPin
, InputPin
, withInputPin
, readInputPin
, getInputPinInputMode
, getInputPinActiveLevel
, setInputPinActiveLevel
, toggleInputPinActiveLevel
, InterruptPin
, withInterruptPin
, readInterruptPin
, pollInterruptPin
, pollInterruptPinTimeout
, getInterruptPinInputMode
, getInterruptPinInterruptMode
, setInterruptPinInterruptMode
, getInterruptPinActiveLevel
, setInterruptPinActiveLevel
, toggleInterruptPinActiveLevel
, OutputPin
, withOutputPin
, writeOutputPin
, toggleOutputPin
, readOutputPin
, getOutputPinOutputMode
, getOutputPinActiveLevel
, setOutputPinActiveLevel
, toggleOutputPinActiveLevel
, SomeGpioException(..)
, gpioExceptionToException
, gpioExceptionFromException
) where
import Prelude ()
import Prelude.Compat
import Control.Monad.Catch (MonadMask, MonadThrow, bracket)
import Control.Monad.Catch.Pure (CatchT)
import Control.Monad.Trans.Cont (ContT)
import Control.Monad.Trans.Except (ExceptT)
import Control.Monad.Trans.Reader (ReaderT)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Identity (IdentityT)
import "transformers" Control.Monad.Trans.List (ListT)
import Control.Monad.Trans.Maybe (MaybeT)
import qualified Control.Monad.Trans.RWS.Lazy as LazyRWS (RWST)
import qualified Control.Monad.Trans.RWS.Strict as StrictRWS (RWST)
import qualified Control.Monad.Trans.State.Lazy as LazyState (StateT)
import qualified Control.Monad.Trans.State.Strict as StrictState (StateT)
import qualified Control.Monad.Trans.Writer.Lazy as LazyWriter (WriterT)
import qualified Control.Monad.Trans.Writer.Strict as StrictWriter (WriterT)
import System.GPIO.Types
(Pin(..), PinInputMode(..), PinOutputMode(..), PinCapabilities(..),
PinActiveLevel(..), PinDirection(..), PinInterruptMode(..),
PinValue(..), SomeGpioException(..), gpioExceptionToException,
gpioExceptionFromException, pinNumber)
class Monad m => MonadGpio h m | m -> h where
pins :: m [Pin]
pinCapabilities :: Pin -> m PinCapabilities
openPin :: Pin -> m h
closePin :: h -> m ()
getPinDirection :: h -> m PinDirection
getPinInputMode :: h -> m PinInputMode
setPinInputMode :: h -> PinInputMode -> m ()
getPinOutputMode :: h -> m PinOutputMode
setPinOutputMode :: h -> PinOutputMode -> PinValue -> m ()
readPin :: h -> m PinValue
pollPin :: h -> m PinValue
pollPinTimeout :: h -> Int -> m (Maybe PinValue)
writePin :: h -> PinValue -> m ()
togglePin :: h -> m PinValue
getPinInterruptMode :: h -> m PinInterruptMode
setPinInterruptMode :: h -> PinInterruptMode -> m ()
getPinActiveLevel :: h -> m PinActiveLevel
setPinActiveLevel :: h -> PinActiveLevel -> m ()
togglePinActiveLevel :: h -> m PinActiveLevel
instance (MonadGpio h m) => MonadGpio h (IdentityT m) where
pins = lift pins
pinCapabilities = lift . pinCapabilities
openPin = lift . openPin
closePin = lift . closePin
getPinDirection = lift . getPinDirection
getPinInputMode = lift . getPinInputMode
setPinInputMode h mode = lift $ setPinInputMode h mode
getPinOutputMode = lift . getPinOutputMode
setPinOutputMode h mode v = lift $ setPinOutputMode h mode v
readPin = lift . readPin
pollPin = lift . readPin
pollPinTimeout h to = lift $ pollPinTimeout h to
writePin h v = lift $ writePin h v
togglePin = lift . togglePin
getPinInterruptMode = lift . getPinInterruptMode
setPinInterruptMode h mode = lift $ setPinInterruptMode h mode
getPinActiveLevel = lift . getPinActiveLevel
setPinActiveLevel h v = lift $ setPinActiveLevel h v
togglePinActiveLevel = lift . togglePinActiveLevel
instance (MonadGpio h m) => MonadGpio h (ContT r m) where
pins = lift pins
pinCapabilities = lift . pinCapabilities
openPin = lift . openPin
closePin = lift . closePin
getPinDirection = lift . getPinDirection
getPinInputMode = lift . getPinInputMode
setPinInputMode h mode = lift $ setPinInputMode h mode
getPinOutputMode = lift . getPinOutputMode
setPinOutputMode h mode v = lift $ setPinOutputMode h mode v
readPin = lift . readPin
pollPin = lift . readPin
pollPinTimeout h to = lift $ pollPinTimeout h to
writePin h v = lift $ writePin h v
togglePin = lift . togglePin
getPinInterruptMode = lift . getPinInterruptMode
setPinInterruptMode h mode = lift $ setPinInterruptMode h mode
getPinActiveLevel = lift . getPinActiveLevel
setPinActiveLevel h v = lift $ setPinActiveLevel h v
togglePinActiveLevel = lift . togglePinActiveLevel
instance (MonadGpio h m) => MonadGpio h (CatchT m) where
pins = lift pins
pinCapabilities = lift . pinCapabilities
openPin = lift . openPin
closePin = lift . closePin
getPinDirection = lift . getPinDirection
getPinInputMode = lift . getPinInputMode
setPinInputMode h mode = lift $ setPinInputMode h mode
getPinOutputMode = lift . getPinOutputMode
setPinOutputMode h mode v = lift $ setPinOutputMode h mode v
readPin = lift . readPin
pollPin = lift . readPin
pollPinTimeout h to = lift $ pollPinTimeout h to
writePin h v = lift $ writePin h v
togglePin = lift . togglePin
getPinInterruptMode = lift . getPinInterruptMode
setPinInterruptMode h mode = lift $ setPinInterruptMode h mode
getPinActiveLevel = lift . getPinActiveLevel
setPinActiveLevel h v = lift $ setPinActiveLevel h v
togglePinActiveLevel = lift . togglePinActiveLevel
instance (MonadGpio h m) => MonadGpio h (ExceptT e m) where
pins = lift pins
pinCapabilities = lift . pinCapabilities
openPin = lift . openPin
closePin = lift . closePin
getPinDirection = lift . getPinDirection
getPinInputMode = lift . getPinInputMode
setPinInputMode h mode = lift $ setPinInputMode h mode
getPinOutputMode = lift . getPinOutputMode
setPinOutputMode h mode v = lift $ setPinOutputMode h mode v
readPin = lift . readPin
pollPin = lift . readPin
pollPinTimeout h to = lift $ pollPinTimeout h to
writePin h v = lift $ writePin h v
togglePin = lift . togglePin
getPinInterruptMode = lift . getPinInterruptMode
setPinInterruptMode h mode = lift $ setPinInterruptMode h mode
getPinActiveLevel = lift . getPinActiveLevel
setPinActiveLevel h v = lift $ setPinActiveLevel h v
togglePinActiveLevel = lift . togglePinActiveLevel
instance (MonadGpio h m) => MonadGpio h (ListT m) where
pins = lift pins
pinCapabilities = lift . pinCapabilities
openPin = lift . openPin
closePin = lift . closePin
getPinDirection = lift . getPinDirection
getPinInputMode = lift . getPinInputMode
setPinInputMode h mode = lift $ setPinInputMode h mode
getPinOutputMode = lift . getPinOutputMode
setPinOutputMode h mode v = lift $ setPinOutputMode h mode v
readPin = lift . readPin
pollPin = lift . readPin
pollPinTimeout h to = lift $ pollPinTimeout h to
writePin h v = lift $ writePin h v
togglePin = lift . togglePin
getPinInterruptMode = lift . getPinInterruptMode
setPinInterruptMode h mode = lift $ setPinInterruptMode h mode
getPinActiveLevel = lift . getPinActiveLevel
setPinActiveLevel h v = lift $ setPinActiveLevel h v
togglePinActiveLevel = lift . togglePinActiveLevel
instance (MonadGpio h m) => MonadGpio h (MaybeT m) where
pins = lift pins
pinCapabilities = lift . pinCapabilities
openPin = lift . openPin
closePin = lift . closePin
getPinDirection = lift . getPinDirection
getPinInputMode = lift . getPinInputMode
setPinInputMode h mode = lift $ setPinInputMode h mode
getPinOutputMode = lift . getPinOutputMode
setPinOutputMode h mode v = lift $ setPinOutputMode h mode v
readPin = lift . readPin
pollPin = lift . readPin
pollPinTimeout h to = lift $ pollPinTimeout h to
writePin h v = lift $ writePin h v
togglePin = lift . togglePin
getPinInterruptMode = lift . getPinInterruptMode
setPinInterruptMode h mode = lift $ setPinInterruptMode h mode
getPinActiveLevel = lift . getPinActiveLevel
setPinActiveLevel h v = lift $ setPinActiveLevel h v
togglePinActiveLevel = lift . togglePinActiveLevel
instance (MonadGpio h m) => MonadGpio h (ReaderT r m) where
pins = lift pins
pinCapabilities = lift . pinCapabilities
openPin = lift . openPin
closePin = lift . closePin
getPinDirection = lift . getPinDirection
getPinInputMode = lift . getPinInputMode
setPinInputMode h mode = lift $ setPinInputMode h mode
getPinOutputMode = lift . getPinOutputMode
setPinOutputMode h mode v = lift $ setPinOutputMode h mode v
readPin = lift . readPin
pollPin = lift . readPin
pollPinTimeout h to = lift $ pollPinTimeout h to
writePin h v = lift $ writePin h v
togglePin = lift . togglePin
getPinInterruptMode = lift . getPinInterruptMode
setPinInterruptMode h mode = lift $ setPinInterruptMode h mode
getPinActiveLevel = lift . getPinActiveLevel
setPinActiveLevel h v = lift $ setPinActiveLevel h v
togglePinActiveLevel = lift . togglePinActiveLevel
instance (MonadGpio h m, Monoid w) => MonadGpio h (LazyRWS.RWST r w s m) where
pins = lift pins
pinCapabilities = lift . pinCapabilities
openPin = lift . openPin
closePin = lift . closePin
getPinDirection = lift . getPinDirection
getPinInputMode = lift . getPinInputMode
setPinInputMode h mode = lift $ setPinInputMode h mode
getPinOutputMode = lift . getPinOutputMode
setPinOutputMode h mode v = lift $ setPinOutputMode h mode v
readPin = lift . readPin
pollPin = lift . readPin
pollPinTimeout h to = lift $ pollPinTimeout h to
writePin h v = lift $ writePin h v
togglePin = lift . togglePin
getPinInterruptMode = lift . getPinInterruptMode
setPinInterruptMode h mode = lift $ setPinInterruptMode h mode
getPinActiveLevel = lift . getPinActiveLevel
setPinActiveLevel h v = lift $ setPinActiveLevel h v
togglePinActiveLevel = lift . togglePinActiveLevel
instance (MonadGpio h m, Monoid w) => MonadGpio h (StrictRWS.RWST r w s m) where
pins = lift pins
pinCapabilities = lift . pinCapabilities
openPin = lift . openPin
closePin = lift . closePin
getPinDirection = lift . getPinDirection
getPinInputMode = lift . getPinInputMode
setPinInputMode h mode = lift $ setPinInputMode h mode
getPinOutputMode = lift . getPinOutputMode
setPinOutputMode h mode v = lift $ setPinOutputMode h mode v
readPin = lift . readPin
pollPin = lift . readPin
pollPinTimeout h to = lift $ pollPinTimeout h to
writePin h v = lift $ writePin h v
togglePin = lift . togglePin
getPinInterruptMode = lift . getPinInterruptMode
setPinInterruptMode h mode = lift $ setPinInterruptMode h mode
getPinActiveLevel = lift . getPinActiveLevel
setPinActiveLevel h v = lift $ setPinActiveLevel h v
togglePinActiveLevel = lift . togglePinActiveLevel
instance (MonadGpio h m) => MonadGpio h (LazyState.StateT s m) where
pins = lift pins
pinCapabilities = lift . pinCapabilities
openPin = lift . openPin
closePin = lift . closePin
getPinDirection = lift . getPinDirection
getPinInputMode = lift . getPinInputMode
setPinInputMode h mode = lift $ setPinInputMode h mode
getPinOutputMode = lift . getPinOutputMode
setPinOutputMode h mode v = lift $ setPinOutputMode h mode v
readPin = lift . readPin
pollPin = lift . readPin
pollPinTimeout h to = lift $ pollPinTimeout h to
writePin h v = lift $ writePin h v
togglePin = lift . togglePin
getPinInterruptMode = lift . getPinInterruptMode
setPinInterruptMode h mode = lift $ setPinInterruptMode h mode
getPinActiveLevel = lift . getPinActiveLevel
setPinActiveLevel h v = lift $ setPinActiveLevel h v
togglePinActiveLevel = lift . togglePinActiveLevel
instance (MonadGpio h m) => MonadGpio h (StrictState.StateT s m) where
pins = lift pins
pinCapabilities = lift . pinCapabilities
openPin = lift . openPin
closePin = lift . closePin
getPinDirection = lift . getPinDirection
getPinInputMode = lift . getPinInputMode
setPinInputMode h mode = lift $ setPinInputMode h mode
getPinOutputMode = lift . getPinOutputMode
setPinOutputMode h mode v = lift $ setPinOutputMode h mode v
readPin = lift . readPin
pollPin = lift . readPin
pollPinTimeout h to = lift $ pollPinTimeout h to
writePin h v = lift $ writePin h v
togglePin = lift . togglePin
getPinInterruptMode = lift . getPinInterruptMode
setPinInterruptMode h mode = lift $ setPinInterruptMode h mode
getPinActiveLevel = lift . getPinActiveLevel
setPinActiveLevel h v = lift $ setPinActiveLevel h v
togglePinActiveLevel = lift . togglePinActiveLevel
instance (MonadGpio h m, Monoid w) => MonadGpio h (LazyWriter.WriterT w m) where
pins = lift pins
pinCapabilities = lift . pinCapabilities
openPin = lift . openPin
closePin = lift . closePin
getPinDirection = lift . getPinDirection
getPinInputMode = lift . getPinInputMode
setPinInputMode h mode = lift $ setPinInputMode h mode
getPinOutputMode = lift . getPinOutputMode
setPinOutputMode h mode v = lift $ setPinOutputMode h mode v
readPin = lift . readPin
pollPin = lift . readPin
pollPinTimeout h to = lift $ pollPinTimeout h to
writePin h v = lift $ writePin h v
togglePin = lift . togglePin
getPinInterruptMode = lift . getPinInterruptMode
setPinInterruptMode h mode = lift $ setPinInterruptMode h mode
getPinActiveLevel = lift . getPinActiveLevel
setPinActiveLevel h v = lift $ setPinActiveLevel h v
togglePinActiveLevel = lift . togglePinActiveLevel
instance (MonadGpio h m, Monoid w) => MonadGpio h (StrictWriter.WriterT w m) where
pins = lift pins
pinCapabilities = lift . pinCapabilities
openPin = lift . openPin
closePin = lift . closePin
getPinDirection = lift . getPinDirection
getPinInputMode = lift . getPinInputMode
setPinInputMode h mode = lift $ setPinInputMode h mode
getPinOutputMode = lift . getPinOutputMode
setPinOutputMode h mode v = lift $ setPinOutputMode h mode v
readPin = lift . readPin
pollPin = lift . readPin
pollPinTimeout h to = lift $ pollPinTimeout h to
writePin h v = lift $ writePin h v
togglePin = lift . togglePin
getPinInterruptMode = lift . getPinInterruptMode
setPinInterruptMode h mode = lift $ setPinInterruptMode h mode
getPinActiveLevel = lift . getPinActiveLevel
setPinActiveLevel h v = lift $ setPinActiveLevel h v
togglePinActiveLevel = lift . togglePinActiveLevel
withPin :: (MonadMask m, MonadGpio h m) => Pin -> (h -> m a) -> m a
withPin p = bracket (openPin p) closePin
newtype InputPin h =
InputPin {_inputHandle :: h}
deriving (Eq,Show)
maybeSetPinActiveLevel :: (MonadGpio h m) => h -> Maybe PinActiveLevel -> m ()
maybeSetPinActiveLevel _ Nothing = return ()
maybeSetPinActiveLevel h (Just v) = setPinActiveLevel h v
withInputPin :: (MonadMask m, MonadGpio h m) => Pin -> PinInputMode -> Maybe PinActiveLevel -> (InputPin h -> m a) -> m a
withInputPin p mode l action =
withPin p $ \h ->
do setPinInputMode h mode
maybeSetPinActiveLevel h l
action $ InputPin h
readInputPin :: (MonadGpio h m) => InputPin h -> m PinValue
readInputPin p =
readPin (_inputHandle p)
getInputPinInputMode :: (MonadGpio h m) => InputPin h -> m PinInputMode
getInputPinInputMode p =
getPinInputMode (_inputHandle p)
getInputPinActiveLevel :: (MonadGpio h m) => InputPin h -> m PinActiveLevel
getInputPinActiveLevel p =
getPinActiveLevel (_inputHandle p)
setInputPinActiveLevel :: (MonadGpio h m) => InputPin h -> PinActiveLevel -> m ()
setInputPinActiveLevel p =
setPinActiveLevel (_inputHandle p)
toggleInputPinActiveLevel :: (MonadGpio h m) => InputPin h -> m PinActiveLevel
toggleInputPinActiveLevel p =
togglePinActiveLevel (_inputHandle p)
newtype InterruptPin h =
InterruptPin {_interruptHandle :: h}
deriving (Eq,Show)
withInterruptPin :: (MonadMask m, MonadGpio h m) => Pin -> PinInputMode -> PinInterruptMode -> Maybe PinActiveLevel -> (InterruptPin h -> m a) -> m a
withInterruptPin p inputMode interruptMode l action =
withPin p $ \h ->
do setPinInputMode h inputMode
setPinInterruptMode h interruptMode
maybeSetPinActiveLevel h l
action $ InterruptPin h
readInterruptPin :: (MonadGpio h m) => InterruptPin h -> m PinValue
readInterruptPin p =
readPin (_interruptHandle p)
pollInterruptPin :: (MonadGpio h m) => InterruptPin h -> m PinValue
pollInterruptPin p =
pollPin (_interruptHandle p)
pollInterruptPinTimeout :: (MonadGpio h m) => InterruptPin h -> Int -> m (Maybe PinValue)
pollInterruptPinTimeout p =
pollPinTimeout (_interruptHandle p)
getInterruptPinInputMode :: (MonadGpio h m) => InterruptPin h -> m PinInputMode
getInterruptPinInputMode p =
getPinInputMode (_interruptHandle p)
getInterruptPinInterruptMode :: (MonadThrow m, MonadGpio h m) => InterruptPin h -> m PinInterruptMode
getInterruptPinInterruptMode p =
getPinInterruptMode (_interruptHandle p)
setInterruptPinInterruptMode :: (MonadGpio h m) => InterruptPin h -> PinInterruptMode -> m ()
setInterruptPinInterruptMode p =
setPinInterruptMode (_interruptHandle p)
getInterruptPinActiveLevel :: (MonadGpio h m) => InterruptPin h -> m PinActiveLevel
getInterruptPinActiveLevel p =
getPinActiveLevel (_interruptHandle p)
setInterruptPinActiveLevel :: (MonadGpio h m) => InterruptPin h -> PinActiveLevel -> m ()
setInterruptPinActiveLevel p =
setPinActiveLevel (_interruptHandle p)
toggleInterruptPinActiveLevel :: (MonadGpio h m) => InterruptPin h -> m PinActiveLevel
toggleInterruptPinActiveLevel p =
togglePinActiveLevel (_interruptHandle p)
newtype OutputPin h =
OutputPin {_outputHandle :: h}
deriving (Eq,Show)
withOutputPin :: (MonadMask m, MonadGpio h m) => Pin -> PinOutputMode -> Maybe PinActiveLevel -> PinValue -> (OutputPin h -> m a) -> m a
withOutputPin p mode l v action =
withPin p $ \h ->
do maybeSetPinActiveLevel h l
setPinOutputMode h mode v
action $ OutputPin h
writeOutputPin :: (MonadGpio h m) => OutputPin h -> PinValue -> m ()
writeOutputPin p =
writePin (_outputHandle p)
toggleOutputPin :: (MonadGpio h m) => OutputPin h -> m PinValue
toggleOutputPin p =
togglePin (_outputHandle p)
readOutputPin :: (MonadGpio h m) => OutputPin h -> m PinValue
readOutputPin p =
readPin (_outputHandle p)
getOutputPinOutputMode :: (MonadGpio h m) => OutputPin h -> m PinOutputMode
getOutputPinOutputMode p =
getPinOutputMode (_outputHandle p)
getOutputPinActiveLevel :: (MonadGpio h m) => OutputPin h -> m PinActiveLevel
getOutputPinActiveLevel p =
getPinActiveLevel (_outputHandle p)
setOutputPinActiveLevel :: (MonadGpio h m) => OutputPin h -> PinActiveLevel -> m ()
setOutputPinActiveLevel p =
setPinActiveLevel (_outputHandle p)
toggleOutputPinActiveLevel :: (MonadGpio h m) => OutputPin h -> m PinActiveLevel
toggleOutputPinActiveLevel p =
togglePinActiveLevel (_outputHandle p)