[grapefruit] Sampling the record of signals

Wolfgang Jeltsch g9ks157k at acme.softbase.org
Fri Apr 24 13:57:16 EDT 2009


Am Donnerstag, 23. April 2009 18:18 schrieb Wolfgang Jeltsch:
> So what you should do is using record types like this:
>
>     X :& val_1 :& … :& val_n
>
> Then define a new “homegenous signal style” like this:
>
>     data HomSignalStyle (signal :: * -> * -> *) era
>
>     instance Style (HomSignalStyle signal era) where
>
>         type K (HomSignalStyle signal era) = PlainKind
>
>     type instance Value (HomSignalStyle signal era) val = signal era val
>
> Homegenous signal records are now defined to be signal records where not
> only the era but also the signal type (CSignal, SSignal, …) is the same for
> all record fields.

Now I see that you can even generalize that. Homogenous signal records never 
use the signal type independently of the era type but they always use the 
signal type applied to the era type. This application results in a functor. 
So let’s try to generalize our homogenous signal style to a functor style:

    data FunctorStyle (func :: * -> *)

    instance Style (FunctorStyle func) where

        type K (FunctorStyle func) = PlainKind

    type instance Value (FunctorStyle func) val = func val

> Now you can implement the sampling of all record fields:
>
>     samplingTransformerPiece
>         :: DSignal era ()
>         -> TransformerPiece
>                 (HomSignalStyle CSignal era)
>                 (HomSignalStyle SSignal era)
>     samplingTransformerPiece sampler = TransformerPiece $ (sampler #>)
>
>     sampleRecord :: (Record PlainKind record) =>
>             record (HomSignalStyle CSignal era) ->
>             record (HomSignalStyle SSignal era)
>     sampleRecord = Data.Record.map samplingTransformerPiece

Oops, this definition of sampleRecord was wrong. It needs an additional 
argument of type DSignal era () which samplingTransformerPiece is applied to.

However, for the functor style, we can implement a generic lifting function 
instead:

    lift :: (Record PlainKind record) =>
            (forall val. func val -> func' val) ->
            (record (FunctorStyle func) -> record (FunctorStyle func'))
    lift fun = Data.Record.map (TransformerPiece fun)

Then we can implement sampleRecord as follows:

    sampleRecord :: (Record PlainKind record) =>
            DSignal era () ->
            record (FunctorStyle (CSignal era)) -> 
            record (FunctorStyle (SSignal era))
    sampleRecord sampler = lift (sampler #>)

> Warning! All code in this e-mail is untested. :-(

The same for the new code. ;-) 

Best wishes,
Wolfgang



More information about the Grapefruit mailing list