dunai icon indicating copy to clipboard operation
dunai copied to clipboard

`bearriver`: definitions missing

Open ivanperez-keera opened this issue 7 years ago • 36 comments

BearRiver is missing some definitions available in Yampa. Ideally, and this is a big issue, it should include everything.

One should not worry at all about optimisations. Leaks and similar issues should be monitored and addressed systematically later.

ivanperez-keera avatar Oct 22 '17 22:10 ivanperez-keera

I am currently experimenting with refactoring my code-base to Bearriver and need primitives like 'after', 'occationally' and 'repeatedly'. I will implement them and can then add them into Bearriver (and/or Dunai) if required.

thalerjonathan avatar Nov 30 '17 13:11 thalerjonathan

I can recommend using exceptions for that. E.g. repeatedly should go something like this:

import Control.Monad.Trans.MSF.Except

repeatedly diff b = safely $ do
  _ <- try $ proc _ -> do 
     time <- integrate    -< 1
     _      <- throwOn () -< time > diff
     step $ return b
     safe $ repeatedly diff b

Possibly there is an issue commuting ReaderT past ExceptT, see this for inspiration.

turion avatar Nov 30 '17 14:11 turion

I just realised that 'after' is implemented already.

Regarding 'occasionally': Yampa gets its stream of random-numbers from a RandomGen which is passed as an argument to occasionally. With MSFs it would be possible to have a RandT monad somewhere in the stack from which to draw the random-numbers. I guess fixing it in the types would be too restrictive / wouldnt work as we fix the monad stack. A solution would be to have a function which generates a random-number from the existing monad stack - is this possible?

thalerjonathan avatar Nov 30 '17 14:11 thalerjonathan

A clean solution to this would maybe be the following API:

module Control.Monad.Trans.MSF.Rand where

-- MonadRandom
import Control.Monad.Random

-- | Updates the generator every step
runRandS :: MSF (RandT g m) a b -> g -> MSF m a (g, b)

evalRandS  :: MSF (RandT g m) a b -> g -> MSF m a b
evalRandS msf g = runRandS msf g >>> arr snd

turion avatar Nov 30 '17 14:11 turion

Getting a stream of random numbers is then as easy as calling arrM_ getRandom. There should probably be an alias for it then, called getRandomS :: (Random b, MonadRandom m) => MSF m a b.

turion avatar Nov 30 '17 14:11 turion

Here is my naive implementation of occasionally in Yampa style (passing in RandomGen explicitly):

occasionally :: (RandomGen g, Monad m) => g -> Time -> b -> SF m a (Event b)
occasionally g t_avg b
    | t_avg > 0 = MSF (const $ tf g b)
    | otherwise = error "AFRP: occasionally: Non-positive average interval."
  where
    tf :: (RandomGen g, Monad m) => g -> b -> ClockInfo m (Event b, SF m a (Event b))
    tf g b = do
      dt <- ask
      let (r, g') = randomR (0, 1) g
      let p = 1 - exp (-(dt / t_avg))
      let evt = if r < p 
                  then Event b 
                  else NoEvent
      return (evt, MSF (const $ tf g' b))

thalerjonathan avatar Nov 30 '17 14:11 thalerjonathan

Why is there no instance (MonadTrans t, MonadRandom m) => MonadRandom (t m) in the MonadRandom package? This would be really useful for us.

turion avatar Nov 30 '17 14:11 turion

Something like this might work. It would be nicer though to first write a more general purpose thing like getRandomS and then implement occasionally in terms of it. It's discouraged to use the MSF constructor, and you don't need it here (feedback works as well).

turion avatar Nov 30 '17 14:11 turion

What about this implementation:

occasionallyFeedback :: (RandomGen g, Monad m) => g -> Time -> b -> SF m a (Event b)
occasionallyFeedback g t_avg b
    | t_avg > 0 = proc _ -> do
      r <- getRandomS g -< ()
      let p = 1 - exp (-(dt / t_avg))
      if r < p
        then returnA -< Event b
        else returnA -< NoEvent
    | otherwise = error "AFRP: occasionally: Non-positive average interval."

getRandomS :: (RandomGen g, Random b, Monad m) => g -> SF m a b
getRandomS g0 = feedback g0 getRandomSAux
  where
    getRandomSAux = proc (_, g) -> do
      let (r, g') = random g
      returnA -< (r, g')

thalerjonathan avatar Nov 30 '17 14:11 thalerjonathan

Looking good :) do you think you can implement runRandS as well? (Or is it unclear how transformers and MSFs interact?) RandT is basically StateT, so it should be possible to reuse the code from Control.Monad.Trans.MSF.State.

turion avatar Nov 30 '17 15:11 turion

It's not yet clear (I am just beginning to understand Monad Transformers). I want to completely omit the RandomGen argument in occasionally and instead draw from a RandT monad which is somewhere in the monad-transformer stack. I don't know how to set up the correct types so that it has a general solution and works for all monad transformers.

Lets say one has the following:

occasionallyMSF :: RandomGen g => Time -> b -> SF (StateT (AgentOut s m) (Rand g)) a (Event b)

The question is now how to formulate this into a general solution which works for the above SF but also for other SFs which have a RandT somewhere in the stack? I thought about this approach but then this is not compatible with the above SF as StateT comes before Rand (I didn't fully understand the order of transformers):

occasionallyMSFGeneral :: (Monad m, RandomGen g) => Time -> b -> SF (RandT g m) a (Event b)

thalerjonathan avatar Nov 30 '17 17:11 thalerjonathan

For most transformers, there are two aspects: The transformer itself, i.e. RandT, and the corresponding class, i.e. MonadRandom. The class shouldn't care about where RandT is sitting in the stack. (That's what I meant by "there should be an instance (MonadTrans t, MonadRandom m) => MonadRandom (t m)". It says that you can bury a RandT under arbitrary other transformers and still access its functionality.) This means we'd have to implement the following for a completely clean solution:


-- Yep, an orphan instance, sadly. Eventually this should be a pull request to the MonadRandom package.
instance (MonadTrans t, MonadRandom m) => MonadRandom (t m) where
  -- use 'lift' from transformers here

-- | Updates the generator every step
runRandS :: MSF (RandT g m) a b -> g -> MSF m a (g, b)
runRandS = _ -- Hint: Use the isomorphism 'RandT ~ StateT' and then 'Control.Monad.Trans.MSF.State'

evalRandS  :: MSF (RandT g m) a b -> g -> MSF m a b
evalRandS msf g = runRandS msf g >>> arr snd


occasionally :: MonadRandom m => Time -> b -> SF m a (Event b)
occasionally = _ -- You already have this basically

turion avatar Nov 30 '17 18:11 turion

Actually my Feedback implementation was wrong as it used a global variable dt. Here is the correct version:

occasionallyFeedback :: (RandomGen g, Monad m) => g -> Time -> b -> SF m a (Event b)
occasionallyFeedback g t_avg b
    | t_avg > 0 = proc _ -> do
      r <- getRandomS g -< ()
      dt <- timeDelta -< ()
      let p = 1 - exp (-(dt / t_avg))
      if r < p
        then returnA -< Event b
        else returnA -< NoEvent
    | otherwise = error "AFRP: occasionally: Non-positive average interval."

timeDelta :: Monad m => SF m a DTime
timeDelta = arrM_ ask

thalerjonathan avatar Dec 03 '17 13:12 thalerjonathan

Here is the implementation without an explicit RandomGen:

occasionally :: MonadRandom m => Time -> b -> SF m a (Event b)
occasionally t_avg b
  | t_avg > 0 = proc _ -> do
    r <- getRandomRS (0, 1) -< ()
    dt <- timeDelta -< ()
    let p = 1 - exp (-(dt / t_avg))
    if r < p
      then returnA -< Event b
      else returnA -< NoEvent
  | otherwise = error "AFRP: occasionally: Non-positive average interval."

getRandomRS :: (MonadRandom m, Random b) => (b, b) -> SF m a b
getRandomRS r = proc _ -> do
  r <- arrM_ $ getRandomR r -< ()
  returnA -< r 

thalerjonathan avatar Dec 03 '17 13:12 thalerjonathan

And here is the implementation for runRandS (follwing your State implementation):

runRandS :: (RandomGen g, Monad m) => MSF (RandT g m) a b -> g -> MSF m a (g, b)
runRandS msf g = MSF $ \a -> do
  ((b, msf'), g') <- runRandT (unMSF msf a) g
  return ((g', b), runRandS msf' g')

thalerjonathan avatar Dec 03 '17 13:12 thalerjonathan

Looking good! Definitely make a pull request out of this!

Just a few minor stylistic things:

  • We shouldn't say "AFRP" in error messages, but rather just "dunai".
  • I think we do camelCase rather than underscores as in t_avg.
  • -< should be aligned.
  • It's probably more efficient to have the if inside returnA value, i.e.:
returnA -< if r < p then Event b else NoEvent

Like this, it's just a function. Your code is correct nevertheless, but it uses ArrowChoice, which could be slightly slower.

turion avatar Dec 03 '17 16:12 turion

OK, I will start making the transition in my library from Yampa to Dunai / BearRiver tomorrow and will then come up with a few pull requests.

Thanks for the great help and hints, this really helped me to better understand MSFs and Monadic Transformers!

thalerjonathan avatar Dec 03 '17 18:12 thalerjonathan

I created the pull request. I forgot to remove Werror before commiting and Travis failed to run through - removed it and all was OK. Why not compile with Werror?

thalerjonathan avatar Dec 03 '17 23:12 thalerjonathan

Thanks a lot @turion for following along and helping @thalerjonathan with his contribution :)

Thanks, @thalerjonathan for the commits.

I agree with you in principle that it would be a great idea to compile everything with Werror. Some warnings are unavoidable, like orphan instances (which we use). The only solution when using Werror is to instruct GHC, in the cabal file or with GHC option pragmas in the haskell files, to ignore certain kinds of warnings.

Minor suggestion added as a review. I may be wrong. In general, in haskell, whenever you find yourself writing:

a <- someArrow -< b
returnA -< a

or

do
  a <- someMonadicExpression
  return a

consider if you can just write the thing without the a. This is a general rule, but there are exceptions. Variable names help document things. Sometimes the expression (someMonadicExpression) does not clearly state what's going on at the level of abstraction that you may be using in the current file, and a well-named variable sometimes solves the problem.

I would suggest aligning things in general. I believe it tends to help understand code and detect anomalies (we humans are good at noticing what's different). Again, this is not a hard-rule: sometimes aligning things introduces so many spaces that it makes things much harder to read.

Also, trying to stick to a fixed number of spaces for indentation (always 2, or always 4). This is more of a guideline. I have not been able to stick to it 100%, especially because it looks weird in some places, and some Haskell constructs don't make this easy.

As @turion already knows, I try to impose these "rules", but I'm the first to break them :( It's usually by mistake.

I want this to be accepted straight from you without changes, so I've just been super-annoying and added these as comments to the pull request.

Also, I would suggest, in the pull-request commit message, to reference the issue in question:

As discussed (#40).

Alternatively, give a very short description.

Adds occasionally, <something> and <something> (refs #40).

This will create a link from the issue to the commit, and from the commit to the issue.

Thanks!

ivanperez-keera avatar Dec 04 '17 06:12 ivanperez-keera

@ivanperez-keera thanks for your comments and your patience. I totally agree there MUST be a consistent code style in a project where multiple people are working together (or contributing) otherwise everything would fall into chaos. I try to adapt it as quickly as possible and am grateful for any comments on style and best practices (e.g. point-free style).

thalerjonathan avatar Dec 04 '17 09:12 thalerjonathan

Not at all! Thank you for contributing! Open issues when you find more things need to be added/improved as you use the library :)

ivanperez-keera avatar Dec 04 '17 09:12 ivanperez-keera

Do we have everything from Yampa now or is there still stuff missing? What do we want to have? Should we open separate issues?

turion avatar Dec 11 '17 16:12 turion

Yampa is immensely big. We do not need to have "everything", but only elementary constructs (those that cannot be expressed in terms of others).

I think that's the core, the most generic parallel switch and decoupled switch, and async stuff (there's one async combinator, apparently).

ivanperez-keera avatar Dec 11 '17 17:12 ivanperez-keera

Can you say more precisely? I don't know about asynchronous stuff in Yampa. Maybe we can draw up a short list of modules that we want to have. We can add FRP.Yampa.Random thanks to @thalerjonathan 's contribution as well.

turion avatar Dec 11 '17 17:12 turion

What about reactInit and ReactHandle ? In my application I use it to let GLOSS trigger the next step of my simulation. I know it can be emulated using MVars but I think it would be nice to have it as well or don't you agree @turion @ivanperez-keera ?

thalerjonathan avatar Dec 14 '17 16:12 thalerjonathan

Also what about repeatedly? I could do an implementation of it and of reactInit if required.

thalerjonathan avatar Dec 15 '17 07:12 thalerjonathan

@ivanperez-keera What async combinators are you thinking of?

turion avatar Dec 18 '17 13:12 turion

Let's collect the modules we want to have (feel free to edit this comment).

Must have

Core
Basic
Integration
Loop
Random
Simulation (reactInit, ReactHandle)
Switches
Time

Could have

EventS (repeatedly)
Conditional
Delays
Event
Hybrid
Scan

Don't know

Task

turion avatar Dec 18 '17 15:12 turion

At the moment occasionally requires the Monad type-class to be of MonadRandom which may be a too strong requirement. What about an occasionally_ implementation which takes the random-numbers from an explicitly passed RandomGen, just as Yampa implements it?

thalerjonathan avatar Dec 29 '17 11:12 thalerjonathan

Also, I am in need of pSwitch but only dpSwitchB exists which is too general for me and does not work as my implementation does create and pair-up the input to the MSFs not from the embed function. Shall I attempt an implementation?

thalerjonathan avatar Dec 29 '17 11:12 thalerjonathan

Implementation of occasionally_:

occasionally_ :: (Monad m, RandomGen g) 
              => g 
              -> Time 
              -> b 
              -> SF m a (Event b)
occasionally_ g0 tAvg b 
  | tAvg <= 0 = error "dunai: Non-positive average interval in occasionally."
  | otherwise = proc _ -> do
    r  <- randomStream (0, 1) g0 -< ()
    dt <- arrM_ ask              -< ()
    let p = 1 - exp (-(dt / tAvg))
    returnA -< if r < p then Event b else NoEvent

randomStream :: (RandomGen g, Random b, Monad m) 
             => (b, b) 
             -> g 
             -> SF m a b
randomStream range g0 = loopPre g0 (randomStreamAux range)
  where
    randomStreamAux :: (RandomGen g, Random b, Monad m) 
                    => (b, b) 
                    -> SF m (a, g) (b, g)
    randomStreamAux range = proc (_, g) -> do
      let (r, g') = randomR range g
      returnA -< (r, g')

thalerjonathan avatar Dec 29 '17 11:12 thalerjonathan

I just realised that randomStream is exactly the same as noiseR, which we could add as well to BearRiver.

thalerjonathan avatar Dec 29 '17 11:12 thalerjonathan

An implementation of dpSwitch based on the existing dpSwitchB:

dpSwitch :: (Monad m, Traversable col)
         => (forall sf. (a -> col sf -> col (b, sf)))
         -> col (SF m b c) 
         -> SF m (a, col c) (Event d) 
         -> (col (SF m b c) -> d -> SF m a (col c))
         -> SF m a (col c)
dpSwitch rf sfs sfF sfCs = MSF $ \a -> do
  let bsfs = rf a sfs
  res <- T.mapM (\(b, sf) -> unMSF sf b) bsfs
  let cs   = fmap fst res
      sfs' = fmap snd res
  (e,sfF') <- unMSF sfF (a, cs)
  let ct = case e of
          Event d -> sfCs sfs' d
          NoEvent -> dpSwitch rf sfs' sfF' sfCs
  return (cs, ct)

thalerjonathan avatar Dec 29 '17 12:12 thalerjonathan

At the moment occasionally requires the Monad type-class to be of MonadRandom which may be a too strong requirement. What about an occasionally_ implementation which takes the random-numbers from an explicitly passed RandomGen, just as Yampa implements it?

I think the bearriver modules that correspond to Yampa modules of the same name should expose exactly the same type signatures, i.e. if our occasionally doesn't have the same type signature as Yampa's occasionally, it should be renamed, and Yampa's occasionally implemented in terms of it.

As for your dpSwitch, can you implement it in terms of exceptions? E.g. this is how you might implement switch with exceptions:

import Control.Monad.Trans.MSF.Except

switch :: MSF m a (b, Maybe c) -> (c -> MSF m a b) -> MSF m a b
switch msf handler = safely $ do
  c <- try $ proc a -> do
    (b, mc) <- msf        -< a
    _       <- throwMaybe -< mc -- I believe that Yampa's switch is not delayed
    returnA               -< b
  safe $ handler c

Exceptions should be more powerful than switches, I think. (And if there is a switch that can't be implemented in terms of exceptions, that's an important issue you could report separately.)

Note also that switches are not time sensitive, so I'd be in favour of putting them directly in dunai, in Data.MonadicStreamFunction.Util.

edit: Yampa's switch isn't delayed

turion avatar Dec 29 '17 13:12 turion

I haven't looked and thought about Exceptions yet and need a quick solution as I am working on a paper. At the moment all switches both in Dunai and BearRiver are implemented without Exceptions. Can I create a pull request for my implementation of dpSwitch and you open an issue for re-implementing the existing switches using Exceptions?

thalerjonathan avatar Dec 29 '17 16:12 thalerjonathan

Better not add code that doesn't quite meet the standard in a rash decision. If you have a deadline, I'd recommend this:

  • If you need the the MSF constructor, add new switches to your own fork of bearriver
  • By all means create pull requests against this repository, but don't expect them to be merged in time for your paper
  • If you, or we, or someone else finds time, reimplement switches in terms of exceptions or other primitives and create a pull request

Unrelatedly, I'd really recommend using exceptions. They've improved my code a lot, and I find the principle quite easy to grasp, much simpler than all those different switches. For a first impression, look at this. You can also open a support issue here, and I'll happily show you how to implement things with exceptions.

turion avatar Dec 29 '17 16:12 turion