Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Behavior t = Stream t
- data TypedBehavior p t = TypedBehavior (Behavior t)
- data Event p v = Event v (Stream Bool)
- newtype GenSketch ctx t = GenSketch (WriterT [(TriggerLimit -> Spec, TriggerLimit -> GenFramework ctx)] (State UniqueIds) t)
- class Ord ctx => Context ctx
- class Output ctx o t where
- class Input ctx o t where
- data GenFramework ctx = Framework {}
- newtype UniqueIds = UniqueIds (Map String Integer)
- newtype UniqueId = UniqueId Integer
- data TriggerLimit
- data PinMode
- newtype CLine = CLine {}
- newtype CChunk = CChunk [CLine]
- type family BehaviorToEvent a
- class IsBehavior behavior where
- (@:) :: behavior -> Behavior Bool -> BehaviorToEvent behavior
- data PinCapabilities
- = DigitalIO
- | AnalogInput
- | PWM
- type family IsDigitalIOPin t where ...
- type family IsAnalogInputPin t where ...
- type family IsPWMPin t where ...
- type family HasPinCapability (c :: t) (list :: [t]) :: Bool where ...
- type family SameCapability a b :: Bool where ...
Documentation
type Behavior t = Stream t Source #
A value that changes over time.
This is implemented as a Stream
in the Copilot DSL.
Copilot provides many operations on streams, for example
&&
to combine two streams of Bools.
For documentation on using the Copilot DSL, see https://copilot-language.github.io/
data TypedBehavior p t Source #
A Behavior with an additional phantom type p
.
The Compilot DSL only lets a Stream contain basic C types,
a limitation that Behavior
also has. When more type safely
is needed, this can be used.
Instances
Output ctx o (Event p (Stream v)) => Output ctx o (TypedBehavior p v) Source # | |
Defined in Sketch.FRP.Copilot.Types (=:) :: o -> TypedBehavior p v -> GenSketch ctx () Source # | |
Typed a => IfThenElse (TypedBehavior p) a Source # | |
Defined in Sketch.FRP.Copilot ifThenElse :: Behavior Bool -> TypedBehavior p a -> TypedBehavior p a -> TypedBehavior p a Source # | |
IsBehavior (TypedBehavior p v) Source # | |
Defined in Sketch.FRP.Copilot.Types (@:) :: TypedBehavior p v -> Behavior Bool -> BehaviorToEvent (TypedBehavior p v) Source # | |
type BehaviorToEvent (TypedBehavior p v) Source # | |
Defined in Sketch.FRP.Copilot.Types |
A discrete event, that occurs at particular points in time.
newtype GenSketch ctx t Source #
A sketch, implemented using Copilot.
It's best to think of the Sketch
as a description of the state of the
board at any point in time.
Under the hood, the Sketch
is run in a loop. On each iteration, it first
reads inputs and then updates outputs as needed.
While it is a monad, a Sketch's outputs are not updated in any particular order, because Copilot does not guarantee any order.
This is a generalized Sketch that can operate on any type of context.
GenSketch (WriterT [(TriggerLimit -> Spec, TriggerLimit -> GenFramework ctx)] (State UniqueIds) t) |
Instances
class Output ctx o t where Source #
(=:) :: o -> t -> GenSketch ctx () infixr 1 Source #
Connect a Behavior
or Event
to an Output
led =: blinking
When a Behavior
is used, its current value is written on each
iteration of the Sketch
.
For example, this constantly turns on the LED, even though it will
already be on after the first iteration, because true
is a Behavior
(that is always True).
led =: true
To avoid unncessary work being done, you can use an Event
instead. Then the write only happens at the points in time
when the Event
occurs. To turn a Behavior
into an Event
,
use @:
So to make the LED only be turned on in the first iteration, and allow it to remain on thereafter without doing extra work:
led =: true @: firstIteration
data GenFramework ctx Source #
The framework of a sketch.
This is a generalized Framework that can operate on any type of context.
Framework | |
|
Instances
data TriggerLimit Source #
Instances
A chunk of C code. Identical chunks get deduplicated.
type family BehaviorToEvent a Source #
This type family is open, so it can be extended when adding other data types to the IsBehavior class.
Instances
type BehaviorToEvent (Behavior v) Source # | |
Defined in Sketch.FRP.Copilot.Types | |
type BehaviorToEvent (TypedBehavior p v) Source # | |
Defined in Sketch.FRP.Copilot.Types |
class IsBehavior behavior where Source #
(@:) :: behavior -> Behavior Bool -> BehaviorToEvent behavior Source #
Generate an Event, from some type of behavior,
that only occurs when the Behavior
Bool is True.
Instances
IsBehavior (Behavior v) Source # | |
Defined in Sketch.FRP.Copilot.Types | |
IsBehavior (TypedBehavior p v) Source # | |
Defined in Sketch.FRP.Copilot.Types (@:) :: TypedBehavior p v -> Behavior Bool -> BehaviorToEvent (TypedBehavior p v) Source # |
data PinCapabilities Source #
Instances
Eq PinCapabilities Source # | |
Defined in Sketch.FRP.Copilot.Types (==) :: PinCapabilities -> PinCapabilities -> Bool # (/=) :: PinCapabilities -> PinCapabilities -> Bool # | |
Ord PinCapabilities Source # | |
Defined in Sketch.FRP.Copilot.Types compare :: PinCapabilities -> PinCapabilities -> Ordering # (<) :: PinCapabilities -> PinCapabilities -> Bool # (<=) :: PinCapabilities -> PinCapabilities -> Bool # (>) :: PinCapabilities -> PinCapabilities -> Bool # (>=) :: PinCapabilities -> PinCapabilities -> Bool # max :: PinCapabilities -> PinCapabilities -> PinCapabilities # min :: PinCapabilities -> PinCapabilities -> PinCapabilities # | |
Show PinCapabilities Source # | |
Defined in Sketch.FRP.Copilot.Types showsPrec :: Int -> PinCapabilities -> ShowS # show :: PinCapabilities -> String # showList :: [PinCapabilities] -> ShowS # |
type family IsDigitalIOPin t where ... Source #
IsDigitalIOPin t = 'True ~ If (HasPinCapability 'DigitalIO t) 'True (TypeError ('Text "This Pin does not support digital IO")) |
type family IsAnalogInputPin t where ... Source #
IsAnalogInputPin t = 'True ~ If (HasPinCapability 'AnalogInput t) 'True (TypeError ('Text "This Pin does not support analog input")) |
type family HasPinCapability (c :: t) (list :: [t]) :: Bool where ... Source #
HasPinCapability c '[] = 'False | |
HasPinCapability c (x ': xs) = SameCapability c x || HasPinCapability c xs |
type family SameCapability a b :: Bool where ... Source #
SameCapability 'DigitalIO 'DigitalIO = 'True | |
SameCapability 'AnalogInput 'AnalogInput = 'True | |
SameCapability 'PWM 'PWM = 'True | |
SameCapability _ _ = 'False |