sketch-frp-copilot-1.0.3: Sketch programming with Copilot
Safe HaskellNone
LanguageHaskell2010

Sketch.FRP.Copilot

Synopsis

Documentation

blinking :: Behavior Bool Source #

Use this to make a LED blink on and off.

On each iteration of the Sketch, this changes to the opposite of its previous value.

This is implemented using Copilot's clk, so to get other blinking behaviors, just pick different numbers, or use Copilot Stream combinators.

blinking = clk (period 2) (phase 1)

firstIteration :: Behavior Bool Source #

True on the first iteration of the Sketch, and False thereafter.

frequency :: Integer -> Behavior Bool Source #

Use this to make an event occur 1 time out of n.

This is implemented using Copilot's clk:

frequency = clk (period n) (phase 1)

scheduleB :: (Typed t, Eq t, Context ctx) => Behavior t -> [(t, GenSketch ctx ())] -> GenSketch ctx () Source #

Schedule when to perform different Sketches.

liftB :: (Behavior a -> Behavior r) -> TypedBehavior t a -> Behavior r Source #

Apply a Copilot DSL function to a TypedBehavior.

liftB2 :: (Behavior a -> Behavior b -> Behavior r) -> TypedBehavior t a -> TypedBehavior t b -> Behavior r Source #

Apply a Copilot DSL function to two TypedBehaviors.

whenB :: Context ctx => Behavior Bool -> GenSketch ctx t -> GenSketch ctx t Source #

Limit the effects of a Sketch to times when a Behavior Bool is True.

When applied to =:, this does the same thing as @: but without the FRP style conversion the input Behavior into an Event. So @: is generally better to use than this.

But, this can also be applied to input, to limit how often input gets read. Useful to avoid performing slow input operations on every iteration of a Sketch.

v <- whenB (frequency 10) $ input pin12

(It's best to think of the value returned by that as an Event, but it's currently represented as a Behavior, since the Copilot DSL cannot operate on Events.)

class IfThenElse t a where Source #

Methods

ifThenElse :: Behavior Bool -> t a -> t a -> t a Source #

This allows "if then else" expressions to be written that choose between two Streams, or Behaviors, or TypedBehaviors, or Sketches, when the RebindableSyntax language extension is enabled.

{-# LANGUAGE RebindableSyntax #-}
buttonpressed <- input pin3
if buttonpressed then ... else ...

Instances

Instances details
Typed a => IfThenElse Stream a Source # 
Instance details

Defined in Sketch.FRP.Copilot

Methods

ifThenElse :: Behavior Bool -> Stream a -> Stream a -> Stream a Source #

Context ctx => IfThenElse (GenSketch ctx) () Source # 
Instance details

Defined in Sketch.FRP.Copilot

Methods

ifThenElse :: Behavior Bool -> GenSketch ctx () -> GenSketch ctx () -> GenSketch ctx () Source #

(Context ctx, Typed a) => IfThenElse (GenSketch ctx) (Behavior a) Source # 
Instance details

Defined in Sketch.FRP.Copilot

Typed a => IfThenElse (TypedBehavior p) a Source # 
Instance details

Defined in Sketch.FRP.Copilot

input :: Input ctx o t => o -> GenSketch ctx (Behavior t) Source #

Use this to read a value from a component of the board.

For example, to read a digital value from pin12 and turn on the led when the pin is high:

buttonpressed <- input pin12
led =: buttonpressed

Some pins support multiple types of reads, for example a pin may support a digital read (Bool), and an analog to digital converter read (ADC). In such cases you may need to specify the type of data to read:

v <- input a0 :: Sketch (Behavior ADC)

data MilliSeconds Source #

A stream of milliseconds.

Constructors

MilliSeconds (Stream Word32) 

data MicroSeconds Source #

A stream of microseconds.

Constructors

MicroSeconds (Stream Word32) 

data Delay Source #

Constructors

Delay 

delay :: Delay Source #

Use this to add a delay between each iteration of the Sketch. A Sketch with no delay will run as fast as the hardware can run it.

delay := MilliSeconds (constant 100)