{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module System.GPIO.Linux.Sysfs.Monad
(
MonadSysfs(..)
, PinDescriptor(..)
, SysfsGpioT(..)
, CatchSysfsM
, ThrowSysfsM
, ThrowCatchSysfsM
, sysfsIsPresent
, availablePins
, pinIsExported
, exportPin
, exportPinChecked
, unexportPin
, unexportPinChecked
, pinHasDirection
, readPinDirection
, writePinDirection
, writePinDirectionWithValue
, readPinValue
, pollPinValue
, pollPinValueTimeout
, writePinValue
, pinHasEdge
, readPinEdge
, writePinEdge
, readPinActiveLow
, writePinActiveLow
) where
import Protolude hiding (readFile, writeFile)
import Control.Monad.Base (MonadBase)
import Control.Monad.Catch (MonadCatch, MonadMask, MonadThrow, catchIOError, throwM)
import Control.Monad.Catch.Pure (CatchT)
import Control.Monad.Cont (MonadCont, ContT)
import Control.Monad.Fix (MonadFix)
import Control.Monad.Logger
(LoggingT, MonadLogger, MonadLoggerIO, NoLoggingT)
import Control.Monad.RWS (MonadRWS)
import Control.Monad.Trans.Class (MonadTrans)
import Control.Monad.Trans.Control
(ComposeSt, MonadBaseControl(..), MonadTransControl(..),
defaultLiftBaseWith, defaultRestoreM)
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 Control.Monad.Writer (MonadWriter)
import qualified Data.ByteString.Char8 as C8 (readInt)
import qualified Data.Set as Set (empty, fromList)
import Foreign.C.Types (CInt(..))
import qualified GHC.IO.Exception as IO (IOErrorType(..))
import System.FilePath ((</>), takeFileName)
import System.IO.Error
(IOError, ioeGetErrorType, isAlreadyInUseError,
isDoesNotExistError, isPermissionError)
import System.GPIO.Linux.Sysfs.Types (SysfsEdge(..), SysfsException(..), toPinInterruptMode, toSysfsEdge)
import System.GPIO.Linux.Sysfs.Util
(intToBS, pinActiveLowFileName, pinDirectionFileName,
pinEdgeFileName, pinValueFileName, pinDirName, activeLowToBS,
pinDirectionToBS, pinDirectionValueToBS, sysfsEdgeToBS,
pinValueToBS, sysfsPath, exportFileName, unexportFileName)
import System.GPIO.Monad (MonadGpio(..), withPin)
import System.GPIO.Types
(Pin(..), PinActiveLevel(..), PinCapabilities(..),
PinDirection(..), PinInputMode(..), PinOutputMode(..),
PinValue(..), invertValue)
class (Monad m) => MonadSysfs m where
doesDirectoryExist :: FilePath -> m Bool
doesFileExist :: FilePath -> m Bool
getDirectoryContents :: FilePath -> m [FilePath]
readFile :: FilePath -> m ByteString
writeFile :: FilePath -> ByteString -> m ()
unlockedWriteFile :: FilePath -> ByteString -> m ()
pollFile :: FilePath -> Int -> m CInt
default doesDirectoryExist :: (MonadTrans t, MonadSysfs m', t m' ~ m) =>
FilePath -> m Bool
default doesFileExist :: (MonadTrans t, MonadSysfs m', t m' ~ m) =>
FilePath -> m Bool
default getDirectoryContents :: (MonadTrans t, MonadSysfs m', t m' ~ m) =>
FilePath -> m [FilePath]
default readFile :: (MonadTrans t, MonadSysfs m', t m' ~ m) =>
FilePath -> m ByteString
default writeFile :: (MonadTrans t, MonadSysfs m', t m' ~ m) =>
FilePath -> ByteString -> m ()
default unlockedWriteFile :: (MonadTrans t, MonadSysfs m', t m' ~ m) =>
FilePath -> ByteString -> m ()
default pollFile :: (MonadTrans t, MonadSysfs m', t m' ~ m) =>
FilePath -> Int -> m CInt
doesDirectoryExist = lift . doesDirectoryExist
{-# INLINE doesDirectoryExist #-}
doesFileExist = lift . doesFileExist
{-# INLINE doesFileExist #-}
getDirectoryContents = lift . getDirectoryContents
{-# INLINE getDirectoryContents #-}
readFile = lift . readFile
{-# INLINE readFile #-}
writeFile fn bs = lift $ writeFile fn bs
{-# INLINE writeFile #-}
unlockedWriteFile fn bs = lift $ unlockedWriteFile fn bs
{-# INLINE unlockedWriteFile #-}
pollFile fn timeout = lift $ pollFile fn timeout
{-# INLINE pollFile #-}
instance (MonadSysfs m) => MonadSysfs (IdentityT m)
instance (MonadSysfs m) => MonadSysfs (ContT r m)
instance (MonadSysfs m) => MonadSysfs (CatchT m)
instance (MonadSysfs m) => MonadSysfs (ExceptT e m)
instance (MonadSysfs m) => MonadSysfs (ListT m)
instance (MonadSysfs m) => MonadSysfs (MaybeT m)
instance (MonadSysfs m) => MonadSysfs (ReaderT r m)
instance (MonadSysfs m, Monoid w) => MonadSysfs (LazyRWS.RWST r w s m)
instance (MonadSysfs m, Monoid w) => MonadSysfs (StrictRWS.RWST r w s m)
instance (MonadSysfs m) => MonadSysfs (LazyState.StateT s m)
instance (MonadSysfs m) => MonadSysfs (StrictState.StateT s m)
instance (MonadSysfs m, Monoid w) => MonadSysfs (LazyWriter.WriterT w m)
instance (MonadSysfs m, Monoid w) => MonadSysfs (StrictWriter.WriterT w m)
instance (MonadSysfs m) => MonadSysfs (LoggingT m)
instance (MonadSysfs m) => MonadSysfs (NoLoggingT m)
newtype PinDescriptor =
PinDescriptor {_pin :: Pin}
deriving (Show,Eq,Ord)
newtype SysfsGpioT m a = SysfsGpioT
{ runSysfsGpioT :: m a
} deriving ( Functor
, Alternative
, Applicative
, Monad
, MonadBase b
, MonadFix
, MonadPlus
, MonadThrow
, MonadCatch
, MonadMask
, MonadCont
, MonadIO
, MonadReader r
, MonadError e
, MonadWriter w
, MonadState s
, MonadRWS r w s
, MonadLogger
, MonadLoggerIO
)
instance MonadTrans SysfsGpioT where
lift = SysfsGpioT
instance MonadBaseControl b m => MonadBaseControl b (SysfsGpioT m) where
type StM (SysfsGpioT m) a = ComposeSt SysfsGpioT m a
liftBaseWith = defaultLiftBaseWith
restoreM = defaultRestoreM
{-# INLINABLE liftBaseWith #-}
{-# INLINABLE restoreM #-}
instance MonadTransControl SysfsGpioT where
type StT SysfsGpioT a = a
liftWith f = SysfsGpioT $ f runSysfsGpioT
restoreT = SysfsGpioT
{-# INLINABLE liftWith #-}
{-# INLINABLE restoreT #-}
type CatchSysfsM m = (Functor m, MonadCatch m, MonadSysfs m)
type ThrowSysfsM m = (Functor m, MonadThrow m, MonadSysfs m)
type ThrowCatchSysfsM m = (Functor m, MonadThrow m, MonadCatch m, MonadSysfs m)
instance (MonadMask m, ThrowCatchSysfsM m) => MonadGpio PinDescriptor (SysfsGpioT m) where
pins =
lift sysfsIsPresent >>= \case
False -> return []
True -> lift availablePins
pinCapabilities p =
lift sysfsIsPresent >>= \case
False -> throwM SysfsNotPresent
True ->
withPin p $ \_ ->
do hasDir <- lift $ pinHasDirection p
hasEdge <- lift $ pinHasEdge p
if hasDir
then return $ PinCapabilities (Set.fromList [InputDefault])
(Set.fromList [OutputDefault])
hasEdge
else return $ PinCapabilities Set.empty Set.empty False
openPin p =
lift sysfsIsPresent >>= \case
False -> throwM SysfsNotPresent
True ->
do lift $ exportPin p
return $ PinDescriptor p
closePin (PinDescriptor p) = lift $ unexportPin p
getPinDirection (PinDescriptor p) =
lift $ readPinDirection p
getPinInputMode (PinDescriptor p) =
do dir <- lift $ readPinDirection p
if dir == In
then return InputDefault
else throwM $ InvalidOperation p
setPinInputMode (PinDescriptor p) mode =
if mode == InputDefault
then lift $ writePinDirection p In
else throwM $ UnsupportedInputMode mode p
getPinOutputMode (PinDescriptor p) =
do dir <- lift $ readPinDirection p
if dir == Out
then return OutputDefault
else throwM $ InvalidOperation p
setPinOutputMode (PinDescriptor p) mode v =
if mode == OutputDefault
then lift $ writePinDirectionWithValue p v
else throwM $ UnsupportedOutputMode mode p
readPin (PinDescriptor p) = lift $ readPinValue p
pollPin (PinDescriptor p) = lift $ pollPinValue p
pollPinTimeout (PinDescriptor p) timeout =
lift $ pollPinValueTimeout p timeout
writePin (PinDescriptor p) v =
lift $ writePinValue p v
togglePin h =
do val <- readPin h
let newVal = invertValue val
void $ writePin h newVal
return newVal
getPinInterruptMode (PinDescriptor p) =
do edge <- lift $ readPinEdge p
return $ toPinInterruptMode edge
setPinInterruptMode (PinDescriptor p) mode =
lift $ writePinEdge p $ toSysfsEdge mode
getPinActiveLevel (PinDescriptor p) =
do activeLow <- lift $ readPinActiveLow p
return $ activeLowToActiveLevel activeLow
setPinActiveLevel (PinDescriptor p) l =
lift $ writePinActiveLow p $ activeLevelToActiveLow l
togglePinActiveLevel (PinDescriptor p) =
do toggled <- not <$> lift (readPinActiveLow p)
lift $ writePinActiveLow p toggled
return $ activeLowToActiveLevel toggled
activeLevelToActiveLow :: PinActiveLevel -> Bool
activeLevelToActiveLow ActiveLow = True
activeLevelToActiveLow ActiveHigh = False
activeLowToActiveLevel :: Bool -> PinActiveLevel
activeLowToActiveLevel False = ActiveHigh
activeLowToActiveLevel True = ActiveLow
sysfsIsPresent :: (MonadSysfs m) => m Bool
sysfsIsPresent = doesDirectoryExist sysfsPath
pinIsExported :: (MonadSysfs m) => Pin -> m Bool
pinIsExported = doesDirectoryExist . pinDirName
exportPin :: (CatchSysfsM m) => Pin -> m ()
exportPin pin@(Pin n) =
catchIOError
(unlockedWriteFile exportFileName (intToBS n))
mapIOError
where
mapIOError :: (MonadThrow m) => IOError -> m ()
mapIOError e
| isAlreadyInUseError e = return ()
| isInvalidArgumentError e = throwM $ InvalidPin pin
| isPermissionError e = throwM $ PermissionDenied pin
| otherwise = throwM e
exportPinChecked :: (CatchSysfsM m) => Pin -> m ()
exportPinChecked pin@(Pin n) =
catchIOError
(unlockedWriteFile exportFileName (intToBS n))
mapIOError
where
mapIOError :: (MonadThrow m) => IOError -> m ()
mapIOError e
| isAlreadyInUseError e = throwM $ AlreadyExported pin
| isInvalidArgumentError e = throwM $ InvalidPin pin
| isPermissionError e = throwM $ PermissionDenied pin
| otherwise = throwM e
unexportPin :: (CatchSysfsM m) => Pin -> m ()
unexportPin pin@(Pin n) =
catchIOError
(unlockedWriteFile unexportFileName (intToBS n))
mapIOError
where
mapIOError :: (MonadThrow m) => IOError -> m ()
mapIOError e
| isInvalidArgumentError e = return ()
| isPermissionError e = throwM $ PermissionDenied pin
| otherwise = throwM e
unexportPinChecked :: (CatchSysfsM m) => Pin -> m ()
unexportPinChecked pin@(Pin n) =
catchIOError
(unlockedWriteFile unexportFileName (intToBS n))
mapIOError
where
mapIOError :: (MonadThrow m) => IOError -> m ()
mapIOError e
| isInvalidArgumentError e = throwM $ NotExported pin
| isPermissionError e = throwM $ PermissionDenied pin
| otherwise = throwM e
pinHasDirection :: (ThrowSysfsM m) => Pin -> m Bool
pinHasDirection p =
do exported <- pinIsExported p
if exported
then doesFileExist (pinDirectionFileName p)
else throwM $ NotExported p
readPinDirection :: (ThrowCatchSysfsM m) => Pin -> m PinDirection
readPinDirection p =
catchIOError
(readFile (pinDirectionFileName p) >>= \case
"in\n" -> return In
"out\n" -> return Out
x -> throwM $ UnexpectedDirection p (decodeUtf8 x))
mapIOError
where
mapIOError :: (ThrowSysfsM m) => IOError -> m PinDirection
mapIOError e
| isDoesNotExistError e =
do exported <- pinIsExported p
if exported
then throwM $ NoDirectionAttribute p
else throwM $ NotExported p
| isPermissionError e = throwM $ PermissionDenied p
| otherwise = throwM e
writePinDirection :: (CatchSysfsM m) => Pin -> PinDirection -> m ()
writePinDirection p In =
writeDirection p (pinDirectionToBS In)
writePinDirection p Out =
do resetEdge p
writeDirection p (pinDirectionToBS Out)
writePinDirectionWithValue :: (CatchSysfsM m) => Pin -> PinValue -> m ()
writePinDirectionWithValue p v =
do activeLow <- readPinActiveLow p
let f = if activeLow then invertValue else identity
resetEdge p
writeDirection p (pinDirectionValueToBS $ f v)
resetEdge :: (CatchSysfsM m) => Pin -> m ()
resetEdge p =
maybeReadPinEdge >>= \case
Nothing -> return ()
Just None -> return ()
_ -> writePinEdge p None
where
maybeReadPinEdge :: (CatchSysfsM m) => m (Maybe SysfsEdge)
maybeReadPinEdge =
pinHasEdge p >>= \case
False -> return Nothing
True ->
do edge <- readPinEdge p
return $ Just edge
writeDirection :: (CatchSysfsM m) => Pin -> ByteString -> m ()
writeDirection p bs =
catchIOError
(writeFile (pinDirectionFileName p) bs)
mapIOError
where
mapIOError :: (ThrowSysfsM m) => IOError -> m ()
mapIOError e
| isDoesNotExistError e =
do exported <- pinIsExported p
if exported
then throwM $ NoDirectionAttribute p
else throwM $ NotExported p
| isPermissionError e = throwM $ PermissionDenied p
| otherwise = throwM e
readPinValue :: (ThrowCatchSysfsM m) => Pin -> m PinValue
readPinValue p =
catchIOError
(readFile (pinValueFileName p) >>= \case
"0\n" -> return Low
"1\n" -> return High
x -> throwM $ UnexpectedValue p (decodeUtf8 x))
mapIOError
where
mapIOError :: (ThrowSysfsM m) => IOError -> m PinValue
mapIOError e
| isDoesNotExistError e = throwM $ NotExported p
| isPermissionError e = throwM $ PermissionDenied p
| otherwise = throwM e
pollPinValue :: (ThrowCatchSysfsM m) => Pin -> m PinValue
pollPinValue p =
pollPinValueTimeout p (-1) >>= \case
Just v -> return v
Nothing -> throwM $
InternalError "pollPinValue timed out, and it should not have. Please file a bug at https://github.com/quixoftic/gpio"
pollPinValueTimeout :: (ThrowCatchSysfsM m) => Pin -> Int -> m (Maybe PinValue)
pollPinValueTimeout p timeout =
catchIOError
(do pollResult <- pollFile (pinValueFileName p) timeout
if pollResult > 0
then Just <$> readPinValue p
else return Nothing)
mapIOError
where
mapIOError :: (ThrowSysfsM m) => IOError -> m (Maybe PinValue)
mapIOError e
| isDoesNotExistError e = throwM $ NotExported p
| isPermissionError e = throwM $ PermissionDenied p
| otherwise = throwM e
writePinValue :: (CatchSysfsM m) => Pin -> PinValue -> m ()
writePinValue p v =
catchIOError
(writeFile (pinValueFileName p) (pinValueToBS v))
mapIOError
where
mapIOError :: (ThrowSysfsM m) => IOError -> m ()
mapIOError e
| isDoesNotExistError e = throwM $ NotExported p
| isPermissionError e = throwM $ PermissionDenied p
| otherwise = throwM e
pinHasEdge :: (ThrowSysfsM m) => Pin -> m Bool
pinHasEdge p =
do exported <- pinIsExported p
if exported
then doesFileExist (pinEdgeFileName p)
else throwM $ NotExported p
readPinEdge :: (ThrowCatchSysfsM m) => Pin -> m SysfsEdge
readPinEdge p =
catchIOError
(readFile (pinEdgeFileName p) >>= \case
"none\n" -> return None
"rising\n" -> return Rising
"falling\n" -> return Falling
"both\n" -> return Both
x -> throwM $ UnexpectedEdge p (decodeUtf8 x))
mapIOError
where
mapIOError :: (ThrowSysfsM m) => IOError -> m SysfsEdge
mapIOError e
| isDoesNotExistError e =
do exported <- pinIsExported p
if exported
then throwM $ NoEdgeAttribute p
else throwM $ NotExported p
| isPermissionError e = throwM $ PermissionDenied p
| otherwise = throwM e
writePinEdge :: (CatchSysfsM m) => Pin -> SysfsEdge -> m ()
writePinEdge p v =
catchIOError
(writeFile (pinEdgeFileName p) (sysfsEdgeToBS v))
mapIOError
where
mapIOError :: (ThrowSysfsM m) => IOError -> m ()
mapIOError e
| isDoesNotExistError e =
do exported <- pinIsExported p
if exported
then throwM $ NoEdgeAttribute p
else throwM $ NotExported p
| isInvalidArgumentError e = throwM $ InvalidOperation p
| isPermissionError e = throwM $ PermissionDenied p
| otherwise = throwM e
readPinActiveLow :: (ThrowCatchSysfsM m) => Pin -> m Bool
readPinActiveLow p =
catchIOError
(readFile (pinActiveLowFileName p) >>= \case
"0\n" -> return False
"1\n" -> return True
x -> throwM $ UnexpectedActiveLow p (decodeUtf8 x))
mapIOError
where
mapIOError :: (ThrowSysfsM m) => IOError -> m Bool
mapIOError e
| isDoesNotExistError e = throwM $ NotExported p
| isPermissionError e = throwM $ PermissionDenied p
| otherwise = throwM e
writePinActiveLow :: (CatchSysfsM m) => Pin -> Bool -> m ()
writePinActiveLow p v =
catchIOError
(writeFile (pinActiveLowFileName p) (activeLowToBS v))
mapIOError
where
mapIOError :: (ThrowSysfsM m) => IOError -> m ()
mapIOError e
| isDoesNotExistError e = throwM $ NotExported p
| isPermissionError e = throwM $ PermissionDenied p
| otherwise = throwM e
availablePins :: (ThrowCatchSysfsM m) => m [Pin]
availablePins =
catchIOError
(do sysfsEntries <- getDirectoryContents sysfsPath
let sysfsContents = fmap (sysfsPath </>) sysfsEntries
sysfsDirectories <- filterM doesDirectoryExist sysfsContents
let chipDirs = filter (isPrefixOf "gpiochip" . takeFileName) sysfsDirectories
gpioPins <- mapM pinRange chipDirs
return $ sort $ concat gpioPins)
mapIOError
where
mapIOError :: (ThrowSysfsM m) => IOError -> m [Pin]
mapIOError e
| isDoesNotExistError e = throwM SysfsError
| isPermissionError e = throwM SysfsPermissionDenied
| otherwise = throwM e
readIntFromFile :: (ThrowSysfsM m) => FilePath -> m Int
readIntFromFile f =
do contents <- readFile f
case C8.readInt contents of
Just (n, _) -> return n
Nothing -> throwM $ UnexpectedContents f (decodeUtf8 contents)
pinRange :: (ThrowSysfsM m) => FilePath -> m [Pin]
pinRange chipDir =
do base <- readIntFromFile (chipDir </> "base")
ngpio <- readIntFromFile (chipDir </> "ngpio")
if base >= 0 && ngpio > 0
then return $ fmap Pin [base .. (base + ngpio - 1)]
else return []
isInvalidArgumentErrorType :: IO.IOErrorType -> Bool
isInvalidArgumentErrorType IO.InvalidArgument = True
isInvalidArgumentErrorType _ = False
isInvalidArgumentError :: IOError -> Bool
isInvalidArgumentError = isInvalidArgumentErrorType . ioeGetErrorType