
Hello all, I've been playing with temporal values, i.e. values which change over time at discrete points in time. I thought it would be good to make it an instance of Applicative and I was pleased with the results. I may be re-inventing some of frp here, but hey. Then I wondered how I would replace one Temporal by another at some point in time. Kind of like switching from summer schedule to winter schedule. Or switching channels on the TV, where each channel is a Temporal Image. It seems that by stacking up Temporals in this way, I could theoretically start with sample values and abstract my way up to a symphony. What is unclear to me is the following: when I have two Temporal Ints, I know what (+) <$> does. It operates on the Ints. But when I have Temporal Temporal Ints, then the function before the <$> would operate on the next level, i.e. it has to be a function which accepts a Temporal. But a Temporal Temporal Int can always be flattened into a Temporal Int. So I may just as well ask to apply a function to the bottom level, namely the Ints. How to I choose how deep down I want to reach? And any other guidance will also be much appreciated. Martin

This package is geared toward your specific question.
https://hackage.haskell.org/package/TypeCompose
On Tue, Mar 24, 2015 at 7:02 AM, martin
Hello all,
I've been playing with temporal values, i.e. values which change over time at discrete points in time. I thought it would be good to make it an instance of Applicative and I was pleased with the results. I may be re-inventing some of frp here, but hey.
Then I wondered how I would replace one Temporal by another at some point in time. Kind of like switching from summer schedule to winter schedule. Or switching channels on the TV, where each channel is a Temporal Image.
It seems that by stacking up Temporals in this way, I could theoretically start with sample values and abstract my way up to a symphony. What is unclear to me is the following: when I have two Temporal Ints, I know what (+) <$> does. It operates on the Ints. But when I have Temporal Temporal Ints, then the function before the <$> would operate on the next level, i.e. it has to be a function which accepts a Temporal.
But a Temporal Temporal Int can always be flattened into a Temporal Int. So I may just as well ask to apply a function to the bottom level, namely the Ints.
How to I choose how deep down I want to reach? And any other guidance will also be much appreciated.
Martin _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Hi Martin,
On Tue, Mar 24, 2015 at 10:02 AM, martin
Hello all,
I've been playing with temporal values, i.e. values which change over time at discrete points in time. I thought it would be good to make it an instance of Applicative and I was pleased with the results. I may be re-inventing some of frp here, but hey.
Then I wondered how I would replace one Temporal by another at some point in time. Kind of like switching from summer schedule to winter schedule. Or switching channels on the TV, where each channel is a Temporal Image.
It seems that by stacking up Temporals in this way, I could theoretically start with sample values and abstract my way up to a symphony. What is unclear to me is the following: when I have two Temporal Ints, I know what (+) <$> does. It operates on the Ints. But when I have Temporal Temporal Ints, then the function before the <$> would operate on the next level, i.e. it has to be a function which accepts a Temporal.
But a Temporal Temporal Int can always be flattened into a Temporal Int. So I may just as well ask to apply a function to the bottom level, namely the Ints.
How to I choose how deep down I want to reach? And any other guidance will also be much appreciated.
Have you considered making Temporal a Monad? All monads by definition provide a `join :: m (m a) -> m a` which flattens their nested structure.
Martin _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Have you considered making Temporal a Monad? All monads by definition provide a `join :: m (m a) -> m a` which flattens their nested structure.
Actually `join` is exactly the operation that makes the difference between Monad and Applicative Functor. Monad's binding operation can easily be defined using a combination of `join` and `fmap`: (>>=) m f = join (fmap f m) So my bet is that the answer to the OP's question lies in Monad.

Am 03/24/2015 um 04:13 AM schrieb Chris Wong:
Hi Martin,
On Tue, Mar 24, 2015 at 10:02 AM, martin
wrote: Hello all,
I've been playing with temporal values, i.e. values which change over time at discrete points in time. I thought it would be good to make it an instance of Applicative and I was pleased with the results. I may be re-inventing some of frp here, but hey.
Have you considered making Temporal a Monad? All monads by definition provide a `join :: m (m a) -> m a` which flattens their nested structure.
I just tried that, but I started with join and I wanted to get >>= for free. data Change a = Chg { ct :: Time, -- "change time" cv :: a -- "change value" } data Temporal a = Temporal { td :: a, -- "temporal default" tc :: [Change a] -- "temporal changes" } deriving (Show) -- apply a function to the value of a change cvf :: (a->b) -> Change a -> Change b cvf f e = Chg (ct e) (f $ cv e) instance Functor Temporal where fmap f (Temporal xd xs) = Temporal (f xd) (map (cvf f) xs) I beleive join is a bit too long to post here. But is seems to work with these examples exNat :: Temporal Int exNat = Temporal 0 (map (\x -> Chg (2*x) (fromIntegral x)) [1..100000]) ext2 :: Temporal Int ext2 = Temporal 10 [Chg 5 0] exNested2 = Temporal exNat [Chg 7 ext2] *Main> tJoin exNested2 Temporal {td = 0, tc = [(2,1),(4,2),(6,3),(7,10)]} It starts with exNat but only up to the Time=10 where ext2 is scheduled and adds the default at Time=10. Since ext2 has no further changes after Time=10, this is it. Then I defined Modad as instance Monad Temporal where return x = Temporal x [] ma >>= f = tJoin $ fmap f ma And Applicative instance Applicative Temporal where pure x = Temporal x [] (<*>) = ap But here is what I get *Main> (*) <$> exNat <*> ext2 Temporal {td = 0, tc = [(2,10),(4,20),(6,30),(8,40),(10,50) ... This is NOT what I expected. Before I had a hand-crafted <*> function, and this gave me *Main> (*) <$> exNat <*> ext2 Temporal {td = 0, tc = [(2,10),(4,20),(5,0),(6,0),(8,0) ... You see the values all drop to zero beyond Time=5, because ext2 drops to zero there and I am multiplying. Where do you think things went awry? Do you think its my tJoin function, or is there something wrong in the way I defined those typeclasses with respect to each other? Or did I voilate one of the laws? How could I find out?

I haven't read all the code, but it seems to me that the most likely
candidate is that your old <*> is breaking the applicative laws. <*>
"can't" depend on the values it's applied to (but based on what you said,
it looks like your old <*> was making choices)
On Thu, Mar 26, 2015 at 11:24 AM, martin
Am 03/24/2015 um 04:13 AM schrieb Chris Wong:
Hi Martin,
On Tue, Mar 24, 2015 at 10:02 AM, martin
wrote: Hello all,
I've been playing with temporal values, i.e. values which change over time at discrete points in time. I thought it would be good to make it an instance of Applicative and I was pleased with the results. I may be re-inventing some of frp here, but hey.
Have you considered making Temporal a Monad? All monads by definition provide a `join :: m (m a) -> m a` which flattens their nested structure.
I just tried that, but I started with join and I wanted to get >>= for free.
data Change a = Chg { ct :: Time, -- "change time" cv :: a -- "change value" }
data Temporal a = Temporal { td :: a, -- "temporal default" tc :: [Change a] -- "temporal changes" } deriving (Show)
-- apply a function to the value of a change cvf :: (a->b) -> Change a -> Change b cvf f e = Chg (ct e) (f $ cv e)
instance Functor Temporal where fmap f (Temporal xd xs) = Temporal (f xd) (map (cvf f) xs)
I beleive join is a bit too long to post here. But is seems to work with these examples
exNat :: Temporal Int exNat = Temporal 0 (map (\x -> Chg (2*x) (fromIntegral x)) [1..100000])
ext2 :: Temporal Int ext2 = Temporal 10 [Chg 5 0]
exNested2 = Temporal exNat [Chg 7 ext2]
*Main> tJoin exNested2 Temporal {td = 0, tc = [(2,1),(4,2),(6,3),(7,10)]}
It starts with exNat but only up to the Time=10 where ext2 is scheduled and adds the default at Time=10. Since ext2 has no further changes after Time=10, this is it.
Then I defined Modad as
instance Monad Temporal where return x = Temporal x [] ma >>= f = tJoin $ fmap f ma
And Applicative
instance Applicative Temporal where pure x = Temporal x [] (<*>) = ap
But here is what I get
*Main> (*) <$> exNat <*> ext2 Temporal {td = 0, tc = [(2,10),(4,20),(6,30),(8,40),(10,50) ...
This is NOT what I expected. Before I had a hand-crafted <*> function, and this gave me
*Main> (*) <$> exNat <*> ext2 Temporal {td = 0, tc = [(2,10),(4,20),(5,0),(6,0),(8,0) ...
You see the values all drop to zero beyond Time=5, because ext2 drops to zero there and I am multiplying.
Where do you think things went awry? Do you think its my tJoin function, or is there something wrong in the way I defined those typeclasses with respect to each other? Or did I voilate one of the laws? How could I find out?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

The composition of any 2 Applicatives is itself an applicative functor. So we have liftA2 (<*>) :: (Applicative p, Applicative q) => p (q (a -> b)) -> p (q a) -> p (q b) On 23/03/2015 at 22:02:41 +0100, martin wrote:
But a Temporal Temporal Int can always be flattened into a Temporal Int.
This is simply join, so it's also a Monad. I assume (pure = return) would make its argument time-invariant.
So I may just as well ask to apply a function to the bottom level, namely the Ints.
How to I choose how deep down I want to reach?
Consider what semantics you want. Not knowing the semantics of Temporal and join :: Temporal (Temporal a) -> Temporal a, I can't say for sure, but changing TV channels seems to me a good example of Temporal (Temporal Image), for each channel is a Temporal Image and which is shown itself varies temporally. Analogously, if I have _ :: [[a]], I can fmap (fmap (_ :: a -> b)) :: [[a]] -> [[b]], fmap (_ :: [a] -> [b]) :: [a] -> [b], or fmap (_ :: a -> b) ∘ join :: [[a]] -> [b] it; which I do is a function of the semantics I want. Hope this helps ☺

Hey guys, you made my day. I had considered making it a monad, but I couldn't figure out what a->mb is supposed to mean in this context and so I thought it was just an Applicative Functor. The idea that the presence of join makes it a monad was not obvious to me. Now I can see the light. I can now imagine how I can have a Temporal Schedule which switches from "Winter Schedule" to "Summer Schedule" at June 1st and a function which takes such a schedule and populates it with some Temporal Data. Way cool. Does the rest of the world know that you haskellers can do such things?
@M Farkas-Dyck I assume (pure = return) would make its argument time-invariant.
Exactly!

There are two equivalent definitions of monad: one in terms of (>>=) and
one in terms of fmap and join. Given (>>=), we can define join and fmap as
join :: Monad m => m (m a) -> m a
join x = x >>= id
Given the join and fmap, we can define (>>=) as
(>>=) :: Monad m => m a -> (a -> m b) -> m b
x >>= f = join (fmap f x)
This is why some other languages like Scala call (>>=) flatMap: it's the
combination of flattening (join) and mapping (fmap).
Personally, much of the time, I find join more intuitive for a given monad
than (>>=), but (>>=) is more useful for everyday code so it's included in
the class by default. Recently, there was a move to add join to the class
so that you could choose which one to implement, but that ran into some
technical difficulties and had to be postponed.
As far as time-varying code goes, you were right in your intuition that
it's closely related to FRP. You have, in fact, come up with a type similar
to events in classical FRP—an accomplishment on its own! I found Conal
Elliott's "Push-Pull Functional Reactive Programming"[1] to have a good
overview of existing ideas in this vein, including a discussion of the
relevant Functor/Applicative/Monad instances.
My understanding is that while the monad instance for this temporal type is
well-defined, current libraries do not implement it for performance
reasons. It's difficult to enable this sort of logic without exposing
potential memory leaks, which make practical programming in the style
significantly more difficult. But the conceptual ideas are all entirely
sound!
On Tue, Mar 24, 2015 at 10:17 AM, martin
Hey guys, you made my day.
I had considered making it a monad, but I couldn't figure out what a->mb is supposed to mean in this context and so I thought it was just an Applicative Functor. The idea that the presence of join makes it a monad was not obvious to me.
Now I can see the light. I can now imagine how I can have a Temporal Schedule which switches from "Winter Schedule" to "Summer Schedule" at June 1st and a function which takes such a schedule and populates it with some Temporal Data.
Way cool. Does the rest of the world know that you haskellers can do such things?
@M Farkas-Dyck I assume (pure = return) would make its argument time-invariant.
Exactly!
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Am 03/24/2015 um 06:40 PM schrieb Tikhon Jelvis:
As far as time-varying code goes, you were right in your intuition that it's closely related to FRP. You have, in fact, come up with a type similar to events in classical FRP—an accomplishment on its own!
My temporal type is defined as follows data Change a = Chg { ct :: Time, -- "change time" cv :: a -- "change value" } data Temporal a = Temporal { td :: a, -- "temporal default" tc :: [Change a] -- "temporal changes" } deriving (Show) I started off with "Event" instead of "Change", but found this misleading. Two successive changes with the same value have the same effect as a single change, while for Events in the sense of "left button click" there is a difference between a click and a doubleclick. I don't know if I'll ever have to intersperse Changes from two lists. In that case two successive changes to the same value *will* make a difference, because the second change my undo the effect of an interspersed change. I am still somewhat struggeling with train schedules. I'd love to craft an example with a summer and a winter schedule, but I don't quite know what to use as a value. Intuitively it'd be something like "departure time", but of what? I am not sure if there is a missing piece, or if I just have to turn away from traditional train schedules and us "train on track 1" as the changing value.

On 24/03/2015 at 20:07:00 +0100, martin wrote:
My temporal type is defined as follows
data Change a = Chg { ct :: Time, -- "change time" cv :: a -- "change value" }
data Temporal a = Temporal { td :: a, -- "temporal default" tc :: [Change a] -- "temporal changes" } deriving (Show)
I started off with "Event" instead of "Change", but found this misleading. Two successive changes with the same value have the same effect as a single change, while for Events in the sense of "left button click" there is a difference between a click and a doubleclick.
As you have it, yes. One could alternately define data Change a = Chg { ct :: Time, c :: a -> a } in which case changes would not in general be idempotent, and idempotent changes would have form Chg { ct = _, c = pure _ }.
I don't know if I'll ever have to intersperse Changes from two lists. In that case two successive changes to the same value *will* make a difference, because the second change my undo the effect of an interspersed change.
Seems a good reason to keep multiplicates in the list ☺
I am still somewhat struggeling with train schedules. I'd love to craft an example with a summer and a winter schedule, but I don't quite know what to use as a value. Intuitively it'd be something like "departure time", but of what? I am not sure if there is a missing piece, or if I just have to turn away from traditional train schedules and us "train on track 1" as the changing value.
Each train could have a Temporal Location. Which definition makes sense is a function of what you want to ask of the schedules.
participants (7)
-
Alexander Solla
-
Chris Wong
-
M Farkas-Dyck
-
martin
-
Nikita Volkov
-
Tikhon Jelvis
-
Tony Morris