copilot-language-4.3: A Haskell-embedded DSL for monitoring hard real-time distributed systems.
Safe HaskellSafe
LanguageHaskell2010

Copilot.Language.Operators.Struct

Description

Combinators to deal with streams carrying structs.

We support two kinds of operations on structs: reading the fields of structs and modifying the fields of structs.

To obtain the values of field x of a struct s, you can just write:

expr = s # x

If you want to update it, use instead a double hash to refer to the field. You can either update the field:

expr = s ## x =: 75

To update it by applying a function to it, for example, the function that updates a stream by one unit, just do:

expr = s ## x =$ (+1)
Synopsis

Documentation

class Projectable d s t | d s -> t where Source #

Common interface to manipulate portions of a larger data structure.

A projectable d s t means that it is possible to manipulate a sub-element s of type t carried in a stream of type d.

Associated Types

data Projection d s t Source #

Unapplied projection or element access on a type.

Methods

(=:) :: Projection d s t -> Stream t -> Stream d infixl 8 Source #

Modify the value of a sub-element of a type in a stream of elements of that type.

(=$) :: Projection d s t -> (Stream t -> Stream t) -> Stream d infixl 8 Source #

Update the value of a sub-element of a type in a stream of elements of that type, by applying a function on streams.

Instances

Instances details
(KnownSymbol f, Typed s, Typed t, Struct s) => Projectable s (s -> Field f t) t Source #

Update a stream of structs.

Instance details

Defined in Copilot.Language.Operators.Struct

Associated Types

data Projection s (s -> Field f t) t Source #

Methods

(=:) :: Projection s (s -> Field f t) t -> Stream t -> Stream s Source #

(=$) :: Projection s (s -> Field f t) t -> (Stream t -> Stream t) -> Stream s Source #

(KnownNat n, Typed t) => Projectable (Array n t) (Stream Word32) t Source #

Update a stream of arrays.

Instance details

Defined in Copilot.Language.Operators.Array

Associated Types

data Projection (Array n t) (Stream Word32) t Source #

Methods

(=:) :: Projection (Array n t) (Stream Word32) t -> Stream t -> Stream (Array n t) Source #

(=$) :: Projection (Array n t) (Stream Word32) t -> (Stream t -> Stream t) -> Stream (Array n t) Source #

(#) :: (KnownSymbol f, Typed t, Typed s, Struct s) => Stream s -> (s -> Field f t) -> Stream t Source #

Create a stream that carries a field of a struct in another stream.

This function implements a projection of a field of a struct over time. For example, if a struct of type T has two fields, t1 of type Int and t2 of type Word8, and s is a stream of type Stream T, then s # t2 has type Stream Word8 and contains the values of the t2 field of the structs in s at any point in time.

(##) :: (KnownSymbol f, Typed t, Typed s, Struct s) => Stream s -> (s -> Field f t) -> Projection s (s -> Field f t) t Source #

Pair a stream with a field accessor, without applying it to obtain the value of the field.

This function is needed to refer to a field accessor when the goal is to update the field value, not just to read it.

Orphan instances

(KnownSymbol f, Typed s, Typed t, Struct s) => Projectable s (s -> Field f t) t Source #

Update a stream of structs.

Instance details

Associated Types

data Projection s (s -> Field f t) t Source #

Methods

(=:) :: Projection s (s -> Field f t) t -> Stream t -> Stream s Source #

(=$) :: Projection s (s -> Field f t) t -> (Stream t -> Stream t) -> Stream s Source #