-- | Programming embedded systems with Copilot, in functional reactive style. -- -- This module can be used with any board supported by the Zephyr project. -- -- -- See Copilot.Zephyr.Board.* for board specific modules. {-# LANGUAGE RebindableSyntax #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE ScopedTypeVariables #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Copilot.Zephyr ( -- * Sketch generation zephyr, Sketch, Pin, Zephyr, -- * Functional reactive programming Behavior, TypedBehavior(..), Event, (@:), -- * Inputs Input, input, input', pullup, -- * Outputs Output, (=:), delay, -- * Other types MilliSeconds(..), MicroSeconds(..), IsDigitalIOPin, IsAnalogInputPin, IsPWMPin, -- * Utilities blinking, firstIteration, frequency, sketchSpec, -- * Combinators liftB, liftB2, whenB, scheduleB, ifThenElse, IfThenElse, -- * Copilot DSL -- -- | Most of the Copilot.Language module is re-exported here, -- including a version of the Prelude modified for it. You -- should enable the RebindableSyntax language extension in -- your program to use the Copilot DSL. -- -- > {-# LANGUAGE RebindableSyntax #-} -- -- For documentation on using the Copilot DSL, see -- Stream, module X, ) where import Language.Copilot as X hiding (Stream, ifThenElse) import Language.Copilot (Stream) import Sketch.FRP.Copilot import Copilot.Zephyr.Internals import Copilot.Zephyr.Main import Control.Monad.Writer import qualified Data.Map as M import qualified Data.Set as S -- | Normally when a digital value is read from a `Pin`, it is configured -- without the internal pullup resistor being enabled. Use this to enable -- the pullup register for all reads from the `Pin`. When the board does not -- have an internal pullup resistor, this will have no effect. -- -- Bear in mind that enabling the pullup resistor inverts the value that -- will be read from the pin. -- -- > pullup pin12 pullup :: IsDigitalIOPin t => Pin t -> Sketch () pullup (Pin p) = tell [(\_ -> return (), \_ -> f)] where f = (emptyFramework @Zephyr) { pinmodes = M.singleton p (S.singleton InputPullupMode) }