sketch-frp-copilot-1.0.8: Sketch programming with Copilot
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sketch.FRP.Copilot.Types

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 ctx o (Event p (Stream v)) => Output ctx o (TypedBehavior p v) Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

Methods

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

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

Defined in Sketch.FRP.Copilot

IsBehavior (TypedBehavior p v) Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

type BehaviorToEvent (TypedBehavior p v) Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

data Event p v Source #

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

Constructors

Event v (Stream Bool) 

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.

Instances

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

Defined in Sketch.FRP.Copilot.Types

Methods

get :: GenSketch ctx UniqueIds #

put :: UniqueIds -> GenSketch ctx () #

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

Applicative (GenSketch ctx) Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

Methods

pure :: a -> GenSketch ctx a #

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

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

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

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

Functor (GenSketch ctx) Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

Methods

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

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

Monad (GenSketch ctx) Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

Methods

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

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

return :: a -> GenSketch ctx a #

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

Defined in Sketch.FRP.Copilot

Methods

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

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

Defined in Sketch.FRP.Copilot.Types

Methods

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

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

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

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

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

Defined in Sketch.FRP.Copilot

Monoid (GenSketch ctx ()) Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

Methods

mempty :: GenSketch ctx () #

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

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

Semigroup (GenSketch ctx t) Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

Methods

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

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

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

class Ord ctx => Context ctx Source #

class Output ctx o t where Source #

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

Methods

(=:) :: 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

Instances

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

Defined in Sketch.FRP.Copilot.Types

Methods

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

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

Defined in Sketch.FRP.Copilot.Types

Methods

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

class Input ctx o t where Source #

Methods

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

The list is input to use when simulating the Sketch.

data GenFramework ctx Source #

The framework of a sketch.

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

Constructors

Framework 

Fields

Instances

Instances details
Context ctx => Monoid (GenFramework ctx) Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

Context ctx => Semigroup (GenFramework ctx) Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

Methods

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

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

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

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

Defined in Sketch.FRP.Copilot.Types

Methods

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

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

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

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

newtype UniqueIds Source #

Constructors

UniqueIds (Map String Integer) 

Instances

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

Defined in Sketch.FRP.Copilot.Types

Methods

get :: GenSketch ctx UniqueIds #

put :: UniqueIds -> GenSketch ctx () #

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

newtype UniqueId Source #

Constructors

UniqueId Integer 

data PinMode Source #

Instances

Instances details
Show PinMode Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

Eq PinMode Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

Methods

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

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

Ord PinMode Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

newtype CLine Source #

A line of C code.

Constructors

CLine 

Fields

Instances

Instances details
Show CLine Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

Methods

showsPrec :: Int -> CLine -> ShowS #

show :: CLine -> String #

showList :: [CLine] -> ShowS #

Eq CLine Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

Methods

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

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

Ord CLine Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

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 #

newtype CChunk Source #

A chunk of C code. Identical chunks get deduplicated.

Constructors

CChunk [CLine] 

Instances

Instances details
Monoid CChunk Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

Semigroup CChunk Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

Show CChunk Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

Eq CChunk Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

Methods

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

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

Ord CChunk Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

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 Sketch.FRP.Copilot.Types

type BehaviorToEvent (TypedBehavior p v) Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

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 Sketch.FRP.Copilot.Types

IsBehavior (TypedBehavior p v) Source # 
Instance details

Defined in Sketch.FRP.Copilot.Types

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