copilot-frp-sketch-1.0.0: FRP sketch programming with Copilot
Safe HaskellNone
LanguageHaskell2010

Copilot.FRPSketch.Internals

Synopsis

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.

Constructors

TypedBehavior (Behavior t) 

Instances

Instances details
Output o (Event p (Stream v)) => Output o (TypedBehavior p v) Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Methods

(=:) :: o -> TypedBehavior p v -> GenSketch pinid () Source #

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

Defined in Copilot.FRPSketch

IsBehavior (TypedBehavior p v) Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

type BehaviorToEvent (TypedBehavior p v) Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

data Event p v Source #

A discrete event, that occurs at particular points in time.

Constructors

Event v (Stream Bool) 

newtype GenSketch pinid 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 pinid.

Instances

Instances details
MonadState UniqueIds (GenSketch pinid) Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Methods

get :: GenSketch pinid UniqueIds #

put :: UniqueIds -> GenSketch pinid () #

state :: (UniqueIds -> (a, UniqueIds)) -> GenSketch pinid a #

Monad (GenSketch pinid) Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Methods

(>>=) :: GenSketch pinid a -> (a -> GenSketch pinid b) -> GenSketch pinid b #

(>>) :: GenSketch pinid a -> GenSketch pinid b -> GenSketch pinid b #

return :: a -> GenSketch pinid a #

Functor (GenSketch pinid) Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Methods

fmap :: (a -> b) -> GenSketch pinid a -> GenSketch pinid b #

(<$) :: a -> GenSketch pinid b -> GenSketch pinid a #

Applicative (GenSketch pinid) Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Methods

pure :: a -> GenSketch pinid a #

(<*>) :: GenSketch pinid (a -> b) -> GenSketch pinid a -> GenSketch pinid b #

liftA2 :: (a -> b -> c) -> GenSketch pinid a -> GenSketch pinid b -> GenSketch pinid c #

(*>) :: GenSketch pinid a -> GenSketch pinid b -> GenSketch pinid b #

(<*) :: GenSketch pinid a -> GenSketch pinid b -> GenSketch pinid a #

Ord pinid => IfThenElse (GenSketch pinid) () Source # 
Instance details

Defined in Copilot.FRPSketch

Methods

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

MonadWriter [(TriggerLimit -> Spec, TriggerLimit -> GenFramework pinid)] (GenSketch pinid) Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Methods

writer :: (a, [(TriggerLimit -> Spec, TriggerLimit -> GenFramework pinid)]) -> GenSketch pinid a #

tell :: [(TriggerLimit -> Spec, TriggerLimit -> GenFramework pinid)] -> GenSketch pinid () #

listen :: GenSketch pinid a -> GenSketch pinid (a, [(TriggerLimit -> Spec, TriggerLimit -> GenFramework pinid)]) #

pass :: GenSketch pinid (a, [(TriggerLimit -> Spec, TriggerLimit -> GenFramework pinid)] -> [(TriggerLimit -> Spec, TriggerLimit -> GenFramework pinid)]) -> GenSketch pinid a #

(Ord pinid, Typed a) => IfThenElse (GenSketch pinid) (Behavior a) Source # 
Instance details

Defined in Copilot.FRPSketch

Methods

ifThenElse :: Behavior Bool -> GenSketch pinid (Behavior a) -> GenSketch pinid (Behavior a) -> GenSketch pinid (Behavior a) Source #

Semigroup (GenSketch pinid t) Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Methods

(<>) :: GenSketch pinid t -> GenSketch pinid t -> GenSketch pinid t #

sconcat :: NonEmpty (GenSketch pinid t) -> GenSketch pinid t #

stimes :: Integral b => b -> GenSketch pinid t -> GenSketch pinid t #

Monoid (GenSketch pinid ()) Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Methods

mempty :: GenSketch pinid () #

mappend :: GenSketch pinid () -> GenSketch pinid () -> GenSketch pinid () #

mconcat :: [GenSketch pinid ()] -> GenSketch pinid () #

newtype UniqueIds Source #

Constructors

UniqueIds (Map String Integer) 

Instances

Instances details
MonadState UniqueIds (GenSketch pinid) Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Methods

get :: GenSketch pinid UniqueIds #

put :: UniqueIds -> GenSketch pinid () #

state :: (UniqueIds -> (a, UniqueIds)) -> GenSketch pinid a #

newtype UniqueId Source #

Constructors

UniqueId Integer 

evalSketch :: Ord pinid => GenSketch pinid a -> (Maybe Spec, GenFramework pinid) Source #

whenB :: Ord pinid => Behavior Bool -> GenSketch pinid t -> GenSketch pinid 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.)

getUniqueId :: String -> GenSketch pinid UniqueId Source #

Gets a unique id.

uniqueName :: String -> UniqueId -> String Source #

Generates a unique name.

data GenFramework pinid Source #

The framework of a sketch.

This is a generalized Framework that can operate on any type of pinid.

Constructors

Framework 

Fields

Instances

Instances details
Ord pinid => Semigroup (GenFramework pinid) Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Methods

(<>) :: GenFramework pinid -> GenFramework pinid -> GenFramework pinid #

sconcat :: NonEmpty (GenFramework pinid) -> GenFramework pinid #

stimes :: Integral b => b -> GenFramework pinid -> GenFramework pinid #

Ord pinid => Monoid (GenFramework pinid) Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Methods

mempty :: GenFramework pinid #

mappend :: GenFramework pinid -> GenFramework pinid -> GenFramework pinid #

mconcat :: [GenFramework pinid] -> GenFramework pinid #

MonadWriter [(TriggerLimit -> Spec, TriggerLimit -> GenFramework pinid)] (GenSketch pinid) Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Methods

writer :: (a, [(TriggerLimit -> Spec, TriggerLimit -> GenFramework pinid)]) -> GenSketch pinid a #

tell :: [(TriggerLimit -> Spec, TriggerLimit -> GenFramework pinid)] -> GenSketch pinid () #

listen :: GenSketch pinid a -> GenSketch pinid (a, [(TriggerLimit -> Spec, TriggerLimit -> GenFramework pinid)]) #

pass :: GenSketch pinid (a, [(TriggerLimit -> Spec, TriggerLimit -> GenFramework pinid)] -> [(TriggerLimit -> Spec, TriggerLimit -> GenFramework pinid)]) -> GenSketch pinid a #

newtype CLine Source #

A line of C code.

Constructors

CLine 

Fields

Instances

Instances details
Eq CLine Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Methods

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

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

Ord CLine Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Methods

compare :: CLine -> CLine -> Ordering #

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

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

(>) :: CLine -> CLine -> Bool #

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

max :: CLine -> CLine -> CLine #

min :: CLine -> CLine -> CLine #

Show CLine Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Methods

showsPrec :: Int -> CLine -> ShowS #

show :: CLine -> String #

showList :: [CLine] -> ShowS #

newtype CChunk Source #

A chunk of C code. Identical chunks get deduplicated.

Constructors

CChunk [CLine] 

Instances

Instances details
Eq CChunk Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Methods

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

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

Ord CChunk Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Show CChunk Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Semigroup CChunk Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Monoid CChunk Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

defineTriggerAlias :: String -> GenFramework pinid -> GenSketch pinid (GenFramework pinid, String) Source #

Copilot only supports calling a trigger with a given name once per Spec; the generated C code will fail to build if the same name is used in two triggers. This generates a unique alias that can be used in a trigger.

data MkInputSource pinid t Source #

Constructors

InputSource 

Fields

type family IsDigitalIOPin t where ... Source #

Equations

IsDigitalIOPin t = 'True ~ If (HasPinCapability 'DigitalIO t) 'True (TypeError ('Text "This Pin does not support digital IO")) 

type family IsAnalogInputPin t where ... Source #

Equations

IsAnalogInputPin t = 'True ~ If (HasPinCapability 'AnalogInput t) 'True (TypeError ('Text "This Pin does not support analog input")) 

type family IsPWMPin t where ... Source #

Equations

IsPWMPin t = 'True ~ If (HasPinCapability 'PWM t) 'True (TypeError ('Text "This Pin does not support PWM")) 

type family HasPinCapability (c :: t) (list :: [t]) :: Bool where ... Source #

Equations

HasPinCapability c '[] = 'False 
HasPinCapability c (x ': xs) = SameCapability c x || HasPinCapability c xs 

data PinMode Source #

Instances

Instances details
Eq PinMode Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Methods

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

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

Ord PinMode Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Show PinMode Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

class Output o t where Source #

Things that can have a Behavior or Event output to them.

Methods

(=:) :: o -> t -> GenSketch pinid () 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

Instances

Instances details
Output o (Event () (Stream v)) => Output o (Behavior v) Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Methods

(=:) :: o -> Behavior v -> GenSketch pinid () Source #

Output o (Event p (Stream v)) => Output o (TypedBehavior p v) Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

Methods

(=:) :: o -> TypedBehavior p v -> GenSketch pinid () Source #

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

Instances details
type BehaviorToEvent (Behavior v) Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

type BehaviorToEvent (TypedBehavior p v) Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

class IsBehavior behavior where Source #

Methods

(@:) :: behavior -> Behavior Bool -> BehaviorToEvent behavior Source #

Generate an Event, from some type of behavior, that only occurs when the Behavior Bool is True.

Instances

Instances details
IsBehavior (Behavior v) Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

IsBehavior (TypedBehavior p v) Source # 
Instance details

Defined in Copilot.FRPSketch.Internals

class Input o t where Source #

Methods

input' :: o -> [t] -> GenSketch pinid (Behavior t) Source #

The list is input to use when simulating the Sketch.

input :: Input o t => o -> GenSketch pinid (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)