hpio-0.9.0.7: Monads for GPIO in Haskell

Copyright(c) 2018 Drew Hess
LicenseBSD3
MaintainerDrew Hess <src@drewhess.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellTrustworthy
LanguageHaskell2010

System.GPIO.Types

Contents

Description

Basic GPIO types.

Synopsis

GPIO pins

newtype Pin Source #

A GPIO pin, identified by pin number.

Note that GPIO pin numbering is platform- and runtime-dependent. See the documentation for your particular platform for an explanation of how pin numbers are assigned to physical pins.

Constructors

Pin Int 
Instances
Bounded Pin Source # 
Instance details

Defined in System.GPIO.Types

Methods

minBound :: Pin #

maxBound :: Pin #

Enum Pin Source # 
Instance details

Defined in System.GPIO.Types

Methods

succ :: Pin -> Pin #

pred :: Pin -> Pin #

toEnum :: Int -> Pin #

fromEnum :: Pin -> Int #

enumFrom :: Pin -> [Pin] #

enumFromThen :: Pin -> Pin -> [Pin] #

enumFromTo :: Pin -> Pin -> [Pin] #

enumFromThenTo :: Pin -> Pin -> Pin -> [Pin] #

Eq Pin Source # 
Instance details

Defined in System.GPIO.Types

Methods

(==) :: Pin -> Pin -> Bool #

(/=) :: Pin -> Pin -> Bool #

Data Pin Source # 
Instance details

Defined in System.GPIO.Types

Methods

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

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

toConstr :: Pin -> Constr #

dataTypeOf :: Pin -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Pin Source # 
Instance details

Defined in System.GPIO.Types

Methods

compare :: Pin -> Pin -> Ordering #

(<) :: Pin -> Pin -> Bool #

(<=) :: Pin -> Pin -> Bool #

(>) :: Pin -> Pin -> Bool #

(>=) :: Pin -> Pin -> Bool #

max :: Pin -> Pin -> Pin #

min :: Pin -> Pin -> Pin #

Read Pin Source # 
Instance details

Defined in System.GPIO.Types

Show Pin Source # 
Instance details

Defined in System.GPIO.Types

Methods

showsPrec :: Int -> Pin -> ShowS #

show :: Pin -> String #

showList :: [Pin] -> ShowS #

Ix Pin Source # 
Instance details

Defined in System.GPIO.Types

Methods

range :: (Pin, Pin) -> [Pin] #

index :: (Pin, Pin) -> Pin -> Int #

unsafeIndex :: (Pin, Pin) -> Pin -> Int

inRange :: (Pin, Pin) -> Pin -> Bool #

rangeSize :: (Pin, Pin) -> Int #

unsafeRangeSize :: (Pin, Pin) -> Int

Generic Pin Source # 
Instance details

Defined in System.GPIO.Types

Associated Types

type Rep Pin :: * -> * #

Methods

from :: Pin -> Rep Pin x #

to :: Rep Pin x -> Pin #

Arbitrary Pin Source # 
Instance details

Defined in System.GPIO.Types

Methods

arbitrary :: Gen Pin #

shrink :: Pin -> [Pin] #

type Rep Pin Source # 
Instance details

Defined in System.GPIO.Types

type Rep Pin = D1 (MetaData "Pin" "System.GPIO.Types" "hpio-0.9.0.7-6wTVDAAhQWjGywt4QfvtzA" True) (C1 (MetaCons "Pin" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

data PinInputMode Source #

GPIO pins may support a number of different physical configurations when used as a digital input.

Pins that are capable of input will at least support the InputDefault mode. InputDefault mode is special in that, unlike the other input modes, it does not represent a unique physical configuration, but is simply a pseudonym for another (actual) input mode. Exactly which mode is used by the hardware when InputDefault mode is specified is platform-dependent. By using InputDefaut mode, you are saying that you don't care about the pin's actual configuration, other than the fact that it's being used for input.

Constructors

InputDefault

The pin's default input mode, i.e., the mode used when a more specific mode is not specified

InputFloating

A floating / high-impedance / tri-state mode which uses little power, but when disconnected, may cause the pin's value to be indeterminate

InputPullUp

The pin is connected to an internal pull-up resistor such that, when the pin is disconnected or connected to a floating / high-impedance node, its physical value will be High

InputPullDown

The pin is connected to an internal pull-down resistor such that, when the pin is disconnected or connected to a floating / high-impedance node, its physical value will be Low

Instances
Bounded PinInputMode Source # 
Instance details

Defined in System.GPIO.Types

Enum PinInputMode Source # 
Instance details

Defined in System.GPIO.Types

Eq PinInputMode Source # 
Instance details

Defined in System.GPIO.Types

Data PinInputMode Source # 
Instance details

Defined in System.GPIO.Types

Methods

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

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

toConstr :: PinInputMode -> Constr #

dataTypeOf :: PinInputMode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PinInputMode Source # 
Instance details

Defined in System.GPIO.Types

Read PinInputMode Source # 
Instance details

Defined in System.GPIO.Types

Show PinInputMode Source # 
Instance details

Defined in System.GPIO.Types

Generic PinInputMode Source # 
Instance details

Defined in System.GPIO.Types

Associated Types

type Rep PinInputMode :: * -> * #

type Rep PinInputMode Source # 
Instance details

Defined in System.GPIO.Types

type Rep PinInputMode = D1 (MetaData "PinInputMode" "System.GPIO.Types" "hpio-0.9.0.7-6wTVDAAhQWjGywt4QfvtzA" False) ((C1 (MetaCons "InputDefault" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "InputFloating" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "InputPullUp" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "InputPullDown" PrefixI False) (U1 :: * -> *)))

data PinOutputMode Source #

GPIO pins may support a number of different physical configurations when used as a digital output.

Pins that are capable of output will at least support the OutputDefault mode. OutputDefault mode is special in that, unlike the other output modes, it does not represent a unique physical configuration, but is simply a pseudonym for another (actual) output mode. Exactly which mode is used by the hardware when OutputDefault mode is specified is platform-dependent. By using OutputDefaut mode, you are saying that you don't care about the pin's actual configuration, other than the fact that it's being used for output.

Constructors

OutputDefault

The pin's default output mode, i.e., the mode used when a more specific mode is not specified

OutputPushPull

The output actively drives both the High and Low states

OutputOpenDrain

The output actively drives the Low state, but High is left floating (also known as open collector)

OutputOpenDrainPullUp

The output actively drives the Low state, and is connected to an internal pull-up resistor in the High state.

OutputOpenSource

The output actively drives the High state, but Low is left floating (also known as open emitter)

OutputOpenSourcePullDown

The output actively drives the High state, and is connected to an internal pull-down resistor in the Low state.

Instances
Bounded PinOutputMode Source # 
Instance details

Defined in System.GPIO.Types

Enum PinOutputMode Source # 
Instance details

Defined in System.GPIO.Types

Eq PinOutputMode Source # 
Instance details

Defined in System.GPIO.Types

Data PinOutputMode Source # 
Instance details

Defined in System.GPIO.Types

Methods

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

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

toConstr :: PinOutputMode -> Constr #

dataTypeOf :: PinOutputMode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PinOutputMode Source # 
Instance details

Defined in System.GPIO.Types

Read PinOutputMode Source # 
Instance details

Defined in System.GPIO.Types

Show PinOutputMode Source # 
Instance details

Defined in System.GPIO.Types

Generic PinOutputMode Source # 
Instance details

Defined in System.GPIO.Types

Associated Types

type Rep PinOutputMode :: * -> * #

type Rep PinOutputMode Source # 
Instance details

Defined in System.GPIO.Types

type Rep PinOutputMode = D1 (MetaData "PinOutputMode" "System.GPIO.Types" "hpio-0.9.0.7-6wTVDAAhQWjGywt4QfvtzA" False) ((C1 (MetaCons "OutputDefault" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OutputPushPull" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OutputOpenDrain" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "OutputOpenDrainPullUp" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OutputOpenSource" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OutputOpenSourcePullDown" PrefixI False) (U1 :: * -> *))))

data PinCapabilities Source #

Catalog a pin's capabilities.

Constructors

PinCapabilities 

Fields

Instances
Eq PinCapabilities Source # 
Instance details

Defined in System.GPIO.Types

Show PinCapabilities Source # 
Instance details

Defined in System.GPIO.Types

Generic PinCapabilities Source # 
Instance details

Defined in System.GPIO.Types

Associated Types

type Rep PinCapabilities :: * -> * #

type Rep PinCapabilities Source # 
Instance details

Defined in System.GPIO.Types

type Rep PinCapabilities = D1 (MetaData "PinCapabilities" "System.GPIO.Types" "hpio-0.9.0.7-6wTVDAAhQWjGywt4QfvtzA" False) (C1 (MetaCons "PinCapabilities" PrefixI True) (S1 (MetaSel (Just "_inputModes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set PinInputMode)) :*: (S1 (MetaSel (Just "_outputModes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set PinOutputMode)) :*: S1 (MetaSel (Just "_interrupts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))

data PinDirection Source #

A pin's direction (input/output).

Constructors

In 
Out 
Instances
Bounded PinDirection Source # 
Instance details

Defined in System.GPIO.Types

Enum PinDirection Source # 
Instance details

Defined in System.GPIO.Types

Eq PinDirection Source # 
Instance details

Defined in System.GPIO.Types

Data PinDirection Source # 
Instance details

Defined in System.GPIO.Types

Methods

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

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

toConstr :: PinDirection -> Constr #

dataTypeOf :: PinDirection -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PinDirection Source # 
Instance details

Defined in System.GPIO.Types

Read PinDirection Source # 
Instance details

Defined in System.GPIO.Types

Show PinDirection Source # 
Instance details

Defined in System.GPIO.Types

Ix PinDirection Source # 
Instance details

Defined in System.GPIO.Types

Generic PinDirection Source # 
Instance details

Defined in System.GPIO.Types

Associated Types

type Rep PinDirection :: * -> * #

Arbitrary PinDirection Source # 
Instance details

Defined in System.GPIO.Types

type Rep PinDirection Source # 
Instance details

Defined in System.GPIO.Types

type Rep PinDirection = D1 (MetaData "PinDirection" "System.GPIO.Types" "hpio-0.9.0.7-6wTVDAAhQWjGywt4QfvtzA" False) (C1 (MetaCons "In" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Out" PrefixI False) (U1 :: * -> *))

data PinActiveLevel Source #

A pin's active level (active-high/active-low).

Constructors

ActiveLow 
ActiveHigh 
Instances
Bounded PinActiveLevel Source # 
Instance details

Defined in System.GPIO.Types

Enum PinActiveLevel Source # 
Instance details

Defined in System.GPIO.Types

Eq PinActiveLevel Source # 
Instance details

Defined in System.GPIO.Types

Data PinActiveLevel Source # 
Instance details

Defined in System.GPIO.Types

Methods

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

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

toConstr :: PinActiveLevel -> Constr #

dataTypeOf :: PinActiveLevel -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PinActiveLevel Source # 
Instance details

Defined in System.GPIO.Types

Read PinActiveLevel Source # 
Instance details

Defined in System.GPIO.Types

Show PinActiveLevel Source # 
Instance details

Defined in System.GPIO.Types

Ix PinActiveLevel Source # 
Instance details

Defined in System.GPIO.Types

Generic PinActiveLevel Source # 
Instance details

Defined in System.GPIO.Types

Associated Types

type Rep PinActiveLevel :: * -> * #

Arbitrary PinActiveLevel Source # 
Instance details

Defined in System.GPIO.Types

type Rep PinActiveLevel Source # 
Instance details

Defined in System.GPIO.Types

type Rep PinActiveLevel = D1 (MetaData "PinActiveLevel" "System.GPIO.Types" "hpio-0.9.0.7-6wTVDAAhQWjGywt4QfvtzA" False) (C1 (MetaCons "ActiveLow" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ActiveHigh" PrefixI False) (U1 :: * -> *))

data PinValue Source #

A pin's signal level as a binary value.

Constructors

Low 
High 
Instances
Bounded PinValue Source # 
Instance details

Defined in System.GPIO.Types

Enum PinValue Source # 
Instance details

Defined in System.GPIO.Types

Eq PinValue Source # 
Instance details

Defined in System.GPIO.Types

Data PinValue Source # 
Instance details

Defined in System.GPIO.Types

Methods

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

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

toConstr :: PinValue -> Constr #

dataTypeOf :: PinValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PinValue Source # 
Instance details

Defined in System.GPIO.Types

Read PinValue Source # 
Instance details

Defined in System.GPIO.Types

Show PinValue Source # 
Instance details

Defined in System.GPIO.Types

Ix PinValue Source # 
Instance details

Defined in System.GPIO.Types

Generic PinValue Source # 
Instance details

Defined in System.GPIO.Types

Associated Types

type Rep PinValue :: * -> * #

Methods

from :: PinValue -> Rep PinValue x #

to :: Rep PinValue x -> PinValue #

Arbitrary PinValue Source # 
Instance details

Defined in System.GPIO.Types

Bits PinValue Source # 
Instance details

Defined in System.GPIO.Types

FiniteBits PinValue Source # 
Instance details

Defined in System.GPIO.Types

type Rep PinValue Source # 
Instance details

Defined in System.GPIO.Types

type Rep PinValue = D1 (MetaData "PinValue" "System.GPIO.Types" "hpio-0.9.0.7-6wTVDAAhQWjGywt4QfvtzA" False) (C1 (MetaCons "Low" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "High" PrefixI False) (U1 :: * -> *))

data PinInterruptMode Source #

A pin's interrupt mode.

Note that the pin's interrupt mode is defined in terms of the pin's logical signal value; i.e., when the pin is configured for active-low logic, RisingEdge refers to the physical signal's trailing edge, and FallingEdge refers to the physical signal's rising edge.

Constructors

Disabled

Interrupts are disabled

RisingEdge

Interrupt on the pin's (logical) rising edge

FallingEdge

Interrupt on the pin's (logical) falling edge

Level

Interrupt on any change to the pin's signal level

Instances
Bounded PinInterruptMode Source # 
Instance details

Defined in System.GPIO.Types

Enum PinInterruptMode Source # 
Instance details

Defined in System.GPIO.Types

Eq PinInterruptMode Source # 
Instance details

Defined in System.GPIO.Types

Data PinInterruptMode Source # 
Instance details

Defined in System.GPIO.Types

Methods

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

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

toConstr :: PinInterruptMode -> Constr #

dataTypeOf :: PinInterruptMode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PinInterruptMode Source # 
Instance details

Defined in System.GPIO.Types

Read PinInterruptMode Source # 
Instance details

Defined in System.GPIO.Types

Show PinInterruptMode Source # 
Instance details

Defined in System.GPIO.Types

Generic PinInterruptMode Source # 
Instance details

Defined in System.GPIO.Types

Associated Types

type Rep PinInterruptMode :: * -> * #

Arbitrary PinInterruptMode Source # 
Instance details

Defined in System.GPIO.Types

type Rep PinInterruptMode Source # 
Instance details

Defined in System.GPIO.Types

type Rep PinInterruptMode = D1 (MetaData "PinInterruptMode" "System.GPIO.Types" "hpio-0.9.0.7-6wTVDAAhQWjGywt4QfvtzA" False) ((C1 (MetaCons "Disabled" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "RisingEdge" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "FallingEdge" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Level" PrefixI False) (U1 :: * -> *)))

Convenience functions

pinNumber :: Pin -> Int Source #

Get the pin number as an Int.

>>> pinNumber (Pin 5)
5

invertDirection :: PinDirection -> PinDirection Source #

Invert a PinDirection value.

>>> invertDirection In
Out
>>> invertDirection Out
In

invertValue :: PinValue -> PinValue Source #

Invert a PinValue.

>>> invertValue High
Low
>>> invertValue Low
High

PinValue conversion to/from Bool

valueToBool :: PinValue -> Bool Source #

Convert a PinValue to its logical boolean equivalent.

>>> valueToBool High
True
>>> valueToBool Low
False

boolToValue :: Bool -> PinValue Source #

Convert a Bool to its logical PinValue equivalent.

>>> boolToValue True
High
>>> boolToValue False
Low

GPIO exceptions